diagrams-core-1.3: Core libraries for diagrams EDSL

Copyright(c) 2011-2015 diagrams-core team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Diagrams.Core.V

Description

Type family for identifying associated vector spaces.

Synopsis

Documentation

type family V a :: * -> * Source

Many sorts of objects have an associated vector space in which they "live". The type function V maps from object types to the associated vector space. The resulting vector space has kind * -> * which means it takes another value (a number) and returns a concrete vector. For example V2 has kind * -> * and V2 Double is a vector.

Instances

type V [a] = V a 
type V (Set a) = V a 
type V (Split m) = V m 
type V (Deletable m) = V m 
type V (Option a) = V a 
type V (TransInv t) = V t 
type V (a -> b) = V b 
type V (a, b) = V a 
type V (Map k a) = V a 
type V (Point v n) = v 
type V ((:+:) m n) = V m 
type V (Measured n a) = V a 
type V (Transformation v n) = v 
type V (Style v n) = v 
type V (Attribute v n) = v 
type V (Trace v n) = v 
type V (Envelope v n) = v 
type V (a, b, c) = V a 
type V (Query v n m) = v 
type V (Prim b v n) = v 
type V (SubMap b v n m) = v 
type V (Subdiagram b v n m) = v 
type V (QDiagram b v n m) = v 

type family N a :: * Source

The numerical field for the object, the number type used for calculations.

Instances

type N [a] = N a 
type N (Set a) = N a 
type N (Split m) = N m 
type N (Deletable m) = N m 
type N (Option a) = N a 
type N (TransInv t) = N t 
type N (a -> b) = N b 
type N (a, b) = N a 
type N (Map k a) = N a 
type N (Point v n) = n 
type N ((:+:) m n) = N m 
type N (Measured n a) = N a 
type N (Transformation v n) = n 
type N (Style v n) = n 
type N (Attribute v n) = n 
type N (Trace v n) = n 
type N (Envelope v n) = n 
type N (a, b, c) = N a 
type N (Query v n m) = n 
type N (Prim b v n) = n 
type N (SubMap b v n m) = n 
type N (Subdiagram b v n m) = n 
type N (QDiagram b v n m) = n 

type Vn a = V a (N a) Source

Conveient type alias to retrieve the vector type associated with an object's vector space. This is usually used as Vn a ~ v n where v is the vector space and n is the numerical field.

class (V a ~ v, N a ~ n, Additive v, Num n) => InSpace v n a Source

InSpace v n a means the type a belongs to the vector space v n, where v is Additive and n is a Num.

Instances

((~) (* -> *) (V a) v, (~) * (N a) n, Additive v, Num n) => InSpace v n a 

class (V a ~ V b, N a ~ N b) => SameSpace a b Source

SameSpace a b means the types a and b belong to the same vector space v n.

Instances

((~) (* -> *) (V a) (V b), (~) * (N a) (N b)) => SameSpace a b