diagrams-core-1.4.1.1: Core libraries for diagrams EDSL

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

Diagrams.Core

Contents

Description

The core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams. Normal users of the diagrams library should almost never need to import anything from this package directly; instead, import modules (especially Diagrams.Prelude) from the diagrams-lib package, which re-exports most things of value to users.

For most library code needing access to core internals, it should be sufficient to import this module, which simply re-exports useful functionality from other modules in the core library. Library writers needing finer-grained access or functionality may occasionally find it useful to directly import one of the constituent core modules.

The diagrams library relies heavily on custom types and classes. Many of the relevant definitions are in the Diagrams.Core.Types module. Indeed the definition of the diagram type QDiagram is contained in: QDiagram.

The best place to start when learning about diagrams' types is the user manual: http://projects.haskell.org/diagrams/doc/manual.html#type-reference The following list shows which types are contained in each module of Diagrams.Core.

Synopsis

Associated vector spaces

type family V a :: * -> * #

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] # 
Instance details

Defined in Diagrams.Core.V

type V [a] = V a
type V (Option a) # 
Instance details

Defined in Diagrams.Core.V

type V (Option a) = V a
type V (Set a) # 
Instance details

Defined in Diagrams.Core.V

type V (Set a) = V a
type V (Split m) # 
Instance details

Defined in Diagrams.Core.V

type V (Split m) = V m
type V (Deletable m) # 
Instance details

Defined in Diagrams.Core.V

type V (Deletable m) = V m
type V (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

type V (TransInv t) = V t
type V (a -> b) # 
Instance details

Defined in Diagrams.Core.V

type V (a -> b) = V b
type V (a, b) # 
Instance details

Defined in Diagrams.Core.V

type V (a, b) = V a
type V (Map k a) # 
Instance details

Defined in Diagrams.Core.V

type V (Map k a) = V a
type V (Point v n) # 
Instance details

Defined in Diagrams.Core.Points

type V (Point v n) = v
type V (m :+: n) # 
Instance details

Defined in Diagrams.Core.V

type V (m :+: n) = V m
type V (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

type V (Measured n a) = V a
type V (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

type V (Transformation v n) = v
type V (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type V (Style v n) = v
type V (Attribute v n) # 
Instance details

Defined in Diagrams.Core.Style

type V (Attribute v n) = v
type V (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

type V (Trace v n) = v
type V (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

type V (Envelope v n) = v
type V (a, b, c) # 
Instance details

Defined in Diagrams.Core.V

type V (a, b, c) = V a
type V (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

type V (Query v n m) = v
type V (Prim b v n) # 
Instance details

Defined in Diagrams.Core.Types

type V (Prim b v n) = v
type V (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type V (SubMap b v n m) = v
type V (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type V (Subdiagram b v n m) = v
type V (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type V (QDiagram b v n m) = v

type family N a :: * #

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

Instances
type N [a] # 
Instance details

Defined in Diagrams.Core.V

type N [a] = N a
type N (Option a) # 
Instance details

Defined in Diagrams.Core.V

type N (Option a) = N a
type N (Set a) # 
Instance details

Defined in Diagrams.Core.V

type N (Set a) = N a
type N (Split m) # 
Instance details

Defined in Diagrams.Core.V

type N (Split m) = N m
type N (Deletable m) # 
Instance details

Defined in Diagrams.Core.V

type N (Deletable m) = N m
type N (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

type N (TransInv t) = N t
type N (a -> b) # 
Instance details

Defined in Diagrams.Core.V

type N (a -> b) = N b
type N (a, b) # 
Instance details

Defined in Diagrams.Core.V

type N (a, b) = N a
type N (Map k a) # 
Instance details

Defined in Diagrams.Core.V

type N (Map k a) = N a
type N (Point v n) # 
Instance details

Defined in Diagrams.Core.Points

type N (Point v n) = n
type N (m :+: n) # 
Instance details

Defined in Diagrams.Core.V

type N (m :+: n) = N m
type N (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

type N (Measured n a) = N a
type N (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

type N (Transformation v n) = n
type N (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type N (Style v n) = n
type N (Attribute v n) # 
Instance details

Defined in Diagrams.Core.Style

type N (Attribute v n) = n
type N (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

type N (Trace v n) = n
type N (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

type N (Envelope v n) = n
type N (a, b, c) # 
Instance details

Defined in Diagrams.Core.V

type N (a, b, c) = N a
type N (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

type N (Query v n m) = n
type N (Prim b v n) # 
Instance details

Defined in Diagrams.Core.Types

type N (Prim b v n) = n
type N (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type N (SubMap b v n m) = n
type N (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type N (Subdiagram b v n m) = n
type N (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type N (QDiagram b v n m) = n

type Vn a = V a (N a) #

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.

type InSpace v n a = (V a ~ v, N a ~ n, Additive v, Num n) #

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

type SameSpace a b = (V a ~ V b, N a ~ N b) #

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

Points

data Point (f :: Type -> Type) a #

A handy wrapper to help distinguish points from vectors at the type level

Instances
Unbox (f a) => Vector Vector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> m (Vector (Point f a)) #

basicUnsafeThaw :: PrimMonad m => Vector (Point f a) -> m (Mutable Vector (PrimState m) (Point f a)) #

basicLength :: Vector (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) #

basicUnsafeIndexM :: Monad m => Vector (Point f a) -> Int -> m (Point f a) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Point f a) -> Vector (Point f a) -> m () #

elemseq :: Vector (Point f a) -> Point f a -> b -> b #

Unbox (f a) => MVector MVector (Point f a) 
Instance details

Defined in Linear.Affine

Methods

basicLength :: MVector s (Point f a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Point f a) -> MVector s (Point f a) #

basicOverlaps :: MVector s (Point f a) -> MVector s (Point f a) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Point f a)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Point f a -> m (MVector (PrimState m) (Point f a)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (Point f a) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> Point f a -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Point f a) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Point f a) -> Point f a -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Point f a) -> MVector (PrimState m) (Point f a) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Point f a) -> Int -> m (MVector (PrimState m) (Point f a)) #

Monad f => Monad (Point f) 
Instance details

Defined in Linear.Affine

Methods

(>>=) :: Point f a -> (a -> Point f b) -> Point f b #

(>>) :: Point f a -> Point f b -> Point f b #

return :: a -> Point f a #

fail :: String -> Point f a #

Functor f => Functor (Point f) 
Instance details

Defined in Linear.Affine

Methods

fmap :: (a -> b) -> Point f a -> Point f b #

(<$) :: a -> Point f b -> Point f a #

Applicative f => Applicative (Point f) 
Instance details

Defined in Linear.Affine

Methods

pure :: a -> Point f a #

(<*>) :: Point f (a -> b) -> Point f a -> Point f b #

liftA2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

(*>) :: Point f a -> Point f b -> Point f b #

(<*) :: Point f a -> Point f b -> Point f a #

Foldable f => Foldable (Point f) 
Instance details

Defined in Linear.Affine

Methods

fold :: Monoid m => Point f m -> m #

foldMap :: Monoid m => (a -> m) -> Point f a -> m #

foldr :: (a -> b -> b) -> b -> Point f a -> b #

foldr' :: (a -> b -> b) -> b -> Point f a -> b #

foldl :: (b -> a -> b) -> b -> Point f a -> b #

foldl' :: (b -> a -> b) -> b -> Point f a -> b #

foldr1 :: (a -> a -> a) -> Point f a -> a #

foldl1 :: (a -> a -> a) -> Point f a -> a #

toList :: Point f a -> [a] #

null :: Point f a -> Bool #

length :: Point f a -> Int #

elem :: Eq a => a -> Point f a -> Bool #

maximum :: Ord a => Point f a -> a #

minimum :: Ord a => Point f a -> a #

sum :: Num a => Point f a -> a #

product :: Num a => Point f a -> a #

Traversable f => Traversable (Point f) 
Instance details

Defined in Linear.Affine

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Point f a -> f0 (Point f b) #

sequenceA :: Applicative f0 => Point f (f0 a) -> f0 (Point f a) #

mapM :: Monad m => (a -> m b) -> Point f a -> m (Point f b) #

sequence :: Monad m => Point f (m a) -> m (Point f a) #

Distributive f => Distributive (Point f) 
Instance details

Defined in Linear.Affine

Methods

distribute :: Functor f0 => f0 (Point f a) -> Point f (f0 a) #

collect :: Functor f0 => (a -> Point f b) -> f0 a -> Point f (f0 b) #

distributeM :: Monad m => m (Point f a) -> Point f (m a) #

collectM :: Monad m => (a -> Point f b) -> m a -> Point f (m b) #

Representable f => Representable (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f) :: Type #

Methods

tabulate :: (Rep (Point f) -> a) -> Point f a #

index :: Point f a -> Rep (Point f) -> a #

Eq1 f => Eq1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftEq :: (a -> b -> Bool) -> Point f a -> Point f b -> Bool #

Ord1 f => Ord1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftCompare :: (a -> b -> Ordering) -> Point f a -> Point f b -> Ordering #

Read1 f => Read1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Point f a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Point f a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Point f a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Point f a] #

Show1 f => Show1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Point f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Point f a] -> ShowS #

Serial1 f => Serial1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () #

deserializeWith :: MonadGet m => m a -> m (Point f a) #

Hashable1 f => Hashable1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Point f a -> Int #

Apply f => Apply (Point f) 
Instance details

Defined in Linear.Affine

Methods

(<.>) :: Point f (a -> b) -> Point f a -> Point f b #

(.>) :: Point f a -> Point f b -> Point f b #

(<.) :: Point f a -> Point f b -> Point f a #

liftF2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Additive f => Affine (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Diff (Point f) :: Type -> Type #

Methods

(.-.) :: Num a => Point f a -> Point f a -> Diff (Point f) a #

(.+^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

(.-^) :: Num a => Point f a -> Diff (Point f) a -> Point f a #

R4 f => R4 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_w :: Lens' (Point f a) a #

_xyzw :: Lens' (Point f a) (V4 a) #

R3 f => R3 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_z :: Lens' (Point f a) a #

_xyz :: Lens' (Point f a) (V3 a) #

R2 f => R2 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_y :: Lens' (Point f a) a #

_xy :: Lens' (Point f a) (V2 a) #

R1 f => R1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

_x :: Lens' (Point f a) a #

Finite f => Finite (Point f) 
Instance details

Defined in Linear.Affine

Associated Types

type Size (Point f) :: Nat #

Methods

toV :: Point f a -> V (Size (Point f)) a #

fromV :: V (Size (Point f)) a -> Point f a #

Metric f => Metric (Point f) 
Instance details

Defined in Linear.Affine

Methods

dot :: Num a => Point f a -> Point f a -> a #

quadrance :: Num a => Point f a -> a #

qd :: Num a => Point f a -> Point f a -> a #

distance :: Floating a => Point f a -> Point f a -> a #

norm :: Floating a => Point f a -> a #

signorm :: Floating a => Point f a -> Point f a #

Additive f => Additive (Point f) 
Instance details

Defined in Linear.Affine

Methods

zero :: Num a => Point f a #

(^+^) :: Num a => Point f a -> Point f a -> Point f a #

(^-^) :: Num a => Point f a -> Point f a -> Point f a #

lerp :: Num a => a -> Point f a -> Point f a -> Point f a #

liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a #

liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c #

Bind f => Bind (Point f) 
Instance details

Defined in Linear.Affine

Methods

(>>-) :: Point f a -> (a -> Point f b) -> Point f b #

join :: Point f (Point f a) -> Point f a #

Generic1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep1 (Point f) :: k -> Type #

Methods

from1 :: Point f a -> Rep1 (Point f) a #

to1 :: Rep1 (Point f) a -> Point f a #

Functor v => Cosieve (Query v) (Point v) # 
Instance details

Defined in Diagrams.Core.Query

Methods

cosieve :: Query v a b -> Point v a -> b #

Eq (f a) => Eq (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(==) :: Point f a -> Point f a -> Bool #

(/=) :: Point f a -> Point f a -> Bool #

Fractional (f a) => Fractional (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(/) :: Point f a -> Point f a -> Point f a #

recip :: Point f a -> Point f a #

fromRational :: Rational -> Point f a #

(Typeable f, Typeable a, Data (f a)) => Data (Point f a) 
Instance details

Defined in Linear.Affine

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Point f a -> c (Point f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a) #

toConstr :: Point f a -> Constr #

dataTypeOf :: Point f a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a)) #

gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) #

Num (f a) => Num (Point f a) 
Instance details

Defined in Linear.Affine

Methods

(+) :: Point f a -> Point f a -> Point f a #

(-) :: Point f a -> Point f a -> Point f a #

(*) :: Point f a -> Point f a -> Point f a #

negate :: Point f a -> Point f a #

abs :: Point f a -> Point f a #

signum :: Point f a -> Point f a #

fromInteger :: Integer -> Point f a #

Ord (f a) => Ord (Point f a) 
Instance details

Defined in Linear.Affine

Methods

compare :: Point f a -> Point f a -> Ordering #

(<) :: Point f a -> Point f a -> Bool #

(<=) :: Point f a -> Point f a -> Bool #

(>) :: Point f a -> Point f a -> Bool #

(>=) :: Point f a -> Point f a -> Bool #

max :: Point f a -> Point f a -> Point f a #

min :: Point f a -> Point f a -> Point f a #

Read (f a) => Read (Point f a) 
Instance details

Defined in Linear.Affine

Show (f a) => Show (Point f a) 
Instance details

Defined in Linear.Affine

Methods

showsPrec :: Int -> Point f a -> ShowS #

show :: Point f a -> String #

showList :: [Point f a] -> ShowS #

Ix (f a) => Ix (Point f a) 
Instance details

Defined in Linear.Affine

Methods

range :: (Point f a, Point f a) -> [Point f a] #

index :: (Point f a, Point f a) -> Point f a -> Int #

unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int

inRange :: (Point f a, Point f a) -> Point f a -> Bool #

rangeSize :: (Point f a, Point f a) -> Int #

unsafeRangeSize :: (Point f a, Point f a) -> Int

Generic (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Rep (Point f a) :: Type -> Type #

Methods

from :: Point f a -> Rep (Point f a) x #

to :: Rep (Point f a) x -> Point f a #

Storable (f a) => Storable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

sizeOf :: Point f a -> Int #

alignment :: Point f a -> Int #

peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a) #

pokeElemOff :: Ptr (Point f a) -> Int -> Point f a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Point f a) #

pokeByteOff :: Ptr b -> Int -> Point f a -> IO () #

peek :: Ptr (Point f a) -> IO (Point f a) #

poke :: Ptr (Point f a) -> Point f a -> IO () #

Binary (f a) => Binary (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Point f a -> Put #

get :: Get (Point f a) #

putList :: [Point f a] -> Put #

Serial (f a) => Serial (Point f a) 
Instance details

Defined in Linear.Affine

Methods

serialize :: MonadPut m => Point f a -> m () #

deserialize :: MonadGet m => m (Point f a) #

Serialize (f a) => Serialize (Point f a) 
Instance details

Defined in Linear.Affine

Methods

put :: Putter (Point f a) #

get :: Get (Point f a) #

NFData (f a) => NFData (Point f a) 
Instance details

Defined in Linear.Affine

Methods

rnf :: Point f a -> () #

Hashable (f a) => Hashable (Point f a) 
Instance details

Defined in Linear.Affine

Methods

hashWithSalt :: Int -> Point f a -> Int #

hash :: Point f a -> Int #

Unbox (f a) => Unbox (Point f a) 
Instance details

Defined in Linear.Affine

Ixed (f a) => Ixed (Point f a) 
Instance details

Defined in Linear.Affine

Methods

ix :: Index (Point f a) -> Traversal' (Point f a) (IxValue (Point f a)) #

Wrapped (Point f a) 
Instance details

Defined in Linear.Affine

Associated Types

type Unwrapped (Point f a) :: Type #

Methods

_Wrapped' :: Iso' (Point f a) (Unwrapped (Point f a)) #

Epsilon (f a) => Epsilon (Point f a) 
Instance details

Defined in Linear.Affine

Methods

nearZero :: Point f a -> Bool #

(Additive v, Num n) => HasOrigin (Point v n) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (Point v n)) (N (Point v n)) -> Point v n -> Point v n #

(Additive v, Num n) => Transformable (Point v n) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (Point v n)) (N (Point v n)) -> Point v n -> Point v n #

(Additive v, Ord n) => Traced (Point v n) #

The trace of a single point is the empty trace, i.e. the one which returns no intersection points for every query. Arguably it should return a single finite distance for vectors aimed directly at the given point, but due to floating-point inaccuracy this is problematic. Note that the envelope for a single point is not the empty envelope (see Diagrams.Core.Envelope).

Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: Point v n -> Trace (V (Point v n)) (N (Point v n)) #

(OrderedField n, Metric v) => Enveloped (Point v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: Point v n -> Envelope (V (Point v n)) (N (Point v n)) #

t ~ Point g b => Rewrapped (Point f a) t 
Instance details

Defined in Linear.Affine

Traversable f => Each (Point f a) (Point f b) a b 
Instance details

Defined in Linear.Affine

Methods

each :: Traversal (Point f a) (Point f b) a b #

newtype MVector s (Point f a) 
Instance details

Defined in Linear.Affine

newtype MVector s (Point f a) = MV_P (MVector s (f a))
type Rep (Point f) 
Instance details

Defined in Linear.Affine

type Rep (Point f) = Rep f
type Diff (Point f) 
Instance details

Defined in Linear.Affine

type Diff (Point f) = f
type Size (Point f) 
Instance details

Defined in Linear.Affine

type Size (Point f) = Size f
type Rep1 (Point f :: Type -> Type) 
Instance details

Defined in Linear.Affine

type Rep1 (Point f :: Type -> Type) = D1 (MetaData "Point" "Linear.Affine" "linear-1.20.8-1XGXa6CyfuLKki79gk8rea" True) (C1 (MetaCons "P" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (Point f a) 
Instance details

Defined in Linear.Affine

type Rep (Point f a) = D1 (MetaData "Point" "Linear.Affine" "linear-1.20.8-1XGXa6CyfuLKki79gk8rea" True) (C1 (MetaCons "P" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))
newtype Vector (Point f a) 
Instance details

Defined in Linear.Affine

newtype Vector (Point f a) = V_P (Vector (f a))
type Index (Point f a) 
Instance details

Defined in Linear.Affine

type Index (Point f a) = Index (f a)
type IxValue (Point f a) 
Instance details

Defined in Linear.Affine

type IxValue (Point f a) = IxValue (f a)
type Unwrapped (Point f a) 
Instance details

Defined in Linear.Affine

type Unwrapped (Point f a) = f a
type N (Point v n) # 
Instance details

Defined in Diagrams.Core.Points

type N (Point v n) = n
type V (Point v n) # 
Instance details

Defined in Diagrams.Core.Points

type V (Point v n) = v

origin :: (Additive f, Num a) => Point f a #

Vector spaces have origins.

(*.) :: (Functor v, Num n) => n -> Point v n -> Point v n #

Scale a point by a scalar. Specialized version of '(*^)'.

relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a) #

An isomorphism between points and vectors, given a reference point.

Transformations

Utilities

basis :: (Additive t, Traversable t, Num a) => [t a] #

Produce a default basis for a vector space. If the dimensionality of the vector space is not statically known, see basisFor.

dimension :: forall a. (Additive (V a), Traversable (V a)) => a -> Int #

Get the dimension of an object whose vector space is an instance of HasLinearMap, e.g. transformations, paths, diagrams, etc.

determinant :: (Additive v, Traversable v, Num n) => Transformation v n -> n #

The determinant of (the linear part of) a Transformation.

isReflection :: (Additive v, Traversable v, Num n, Ord n) => Transformation v n -> Bool #

Determine whether a Transformation includes a reflection component, that is, whether it reverses orientation.

Invertible linear transformations

data u :-: v infixr 7 #

(v1 :-: v2) is a linear map paired with its inverse.

Instances
Semigroup (a :-: a) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

(<>) :: (a :-: a) -> (a :-: a) -> a :-: a #

sconcat :: NonEmpty (a :-: a) -> a :-: a #

stimes :: Integral b => b -> (a :-: a) -> a :-: a #

Monoid (v :-: v) #

Invertible linear maps from a vector space to itself form a monoid under composition.

Instance details

Defined in Diagrams.Core.Transform

Methods

mempty :: v :-: v #

mappend :: (v :-: v) -> (v :-: v) -> v :-: v #

mconcat :: [v :-: v] -> v :-: v #

(<->) :: (u -> v) -> (v -> u) -> u :-: v #

Create an invertible linear map from two functions which are assumed to be linear inverses.

linv :: (u :-: v) -> v :-: u #

Invert a linear map.

lapp :: (u :-: v) -> u -> v #

Apply a linear map to a vector.

General transformations

data Transformation v n #

General (affine) transformations, represented by an invertible linear map, its transpose, and a vector representing a translation component.

By the transpose of a linear map we mean simply the linear map corresponding to the transpose of the map's matrix representation. For example, any scale is its own transpose, since scales are represented by matrices with zeros everywhere except the diagonal. The transpose of a rotation is the same as its inverse.

The reason we need to keep track of transposes is because it turns out that when transforming a shape according to some linear map L, the shape's normal vectors transform according to L's inverse transpose. (For a more detailed explanation and proof, see https://wiki.haskell.org/Diagrams/Dev/Transformations.) This is exactly what we need when transforming bounding functions, which are defined in terms of perpendicular (i.e. normal) hyperplanes.

For more general, non-invertible transformations, see Diagrams.Deform (in diagrams-lib).

Instances
(Additive v, Num n) => Semigroup (Transformation v n) #

Transformations are closed under composition; t1 <> t2 is the transformation which performs first t2, then t1.

Instance details

Defined in Diagrams.Core.Transform

(Additive v, Num n) => Monoid (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

(Additive v, Num n) => HasOrigin (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

(Additive v, Num n) => Transformable (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

(Transformable a, V a ~ v, N a ~ n) => Action (Transformation v n) a #

Transformations can act on transformable things.

Instance details

Defined in Diagrams.Core.Transform

Methods

act :: Transformation v n -> a -> a #

type N (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

type N (Transformation v n) = n
type V (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

type V (Transformation v n) = v

inv :: (Functor v, Num n) => Transformation v n -> Transformation v n #

Invert a transformation.

transp :: Transformation v n -> v n :-: v n #

Get the transpose of a transformation (ignoring the translation component).

transl :: Transformation v n -> v n #

Get the translational component of a transformation.

dropTransl :: (Additive v, Num n) => Transformation v n -> Transformation v n #

Drop the translational component of a transformation, leaving only the linear part.

apply :: Transformation v n -> v n -> v n #

Apply a transformation to a vector. Note that any translational component of the transformation will not affect the vector, since vectors are invariant under translation.

papply :: (Additive v, Num n) => Transformation v n -> Point v n -> Point v n #

Apply a transformation to a point.

fromLinear :: (Additive v, Num n) => (v n :-: v n) -> (v n :-: v n) -> Transformation v n #

Create a general affine transformation from an invertible linear transformation and its transpose. The translational component is assumed to be zero.

Some specific transformations

translation :: v n -> Transformation v n #

Create a translation.

translate :: Transformable t => Vn t -> t -> t #

Translate by a vector.

moveTo :: (InSpace v n t, HasOrigin t) => Point v n -> t -> t #

Translate the object by the translation that sends the origin to the given point. Note that this is dual to moveOriginTo, i.e. we should have

  moveTo (origin .^+ v) === moveOriginTo (origin .^- v)
  

For types which are also Transformable, this is essentially the same as translate, i.e.

  moveTo (origin .^+ v) === translate v
  

place :: (InSpace v n t, HasOrigin t) => t -> Point v n -> t #

A flipped variant of moveTo, provided for convenience. Useful when writing a function which takes a point as an argument, such as when using withName and friends.

scaling :: (Additive v, Fractional n) => n -> Transformation v n #

Create a uniform scaling transformation.

scale :: (InSpace v n a, Eq n, Fractional n, Transformable a) => n -> a -> a #

Scale uniformly in every dimension by the given scalar.

avgScale :: (Additive v, Traversable v, Floating n) => Transformation v n -> n #

Compute the "average" amount of scaling performed by a transformation. Satisfies the properties

  avgScale (scaling k) == k
  avgScale (t1 <> t2)  == avgScale t1 * avgScale t2
  

The Transformable class

class Transformable t where #

Type class for things t which can be transformed.

Methods

transform :: Transformation (V t) (N t) -> t -> t #

Apply a transformation to an object.

Instances
Transformable t => Transformable [t] # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V [t]) (N [t]) -> [t] -> [t] #

(Transformable t, Ord t) => Transformable (Set t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (Set t)) (N (Set t)) -> Set t -> Set t #

Transformable m => Transformable (Deletable m) # 
Instance details

Defined in Diagrams.Core.Transform

(Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (TransInv t)) (N (TransInv t)) -> TransInv t -> TransInv t #

(V t ~ v, N t ~ n, V t ~ V s, N t ~ N s, Functor v, Num n, Transformable t, Transformable s) => Transformable (s -> t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (s -> t)) (N (s -> t)) -> (s -> t) -> s -> t #

(Transformable t, Transformable s, V t ~ V s, N t ~ N s) => Transformable (t, s) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (t, s)) (N (t, s)) -> (t, s) -> (t, s) #

Transformable t => Transformable (Map k t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (Map k t)) (N (Map k t)) -> Map k t -> Map k t #

(Additive v, Num n) => Transformable (Point v n) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (Point v n)) (N (Point v n)) -> Point v n -> Point v n #

(InSpace v n t, Transformable t, HasLinearMap v, Floating n) => Transformable (Measured n t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (Measured n t)) (N (Measured n t)) -> Measured n t -> Measured n t #

(Additive v, Num n) => Transformable (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

(Additive v, Traversable v, Floating n) => Transformable (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Methods

transform :: Transformation (V (Style v n)) (N (Style v n)) -> Style v n -> Style v n #

(Additive v, Traversable v, Floating n) => Transformable (Attribute v n) #

TAttributes are transformed directly, MAttributes have their local scale multiplied by the average scale of the transform. Plain Attributes are unaffected.

Instance details

Defined in Diagrams.Core.Style

Methods

transform :: Transformation (V (Attribute v n)) (N (Attribute v n)) -> Attribute v n -> Attribute v n #

(Additive v, Num n) => Transformable (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

transform :: Transformation (V (Trace v n)) (N (Trace v n)) -> Trace v n -> Trace v n #

(Metric v, Floating n) => Transformable (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

transform :: Transformation (V (Envelope v n)) (N (Envelope v n)) -> Envelope v n -> Envelope v n #

(Transformable t, Transformable s, Transformable u, V s ~ V t, N s ~ N t, V s ~ V u, N s ~ N u) => Transformable (t, s, u) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (t, s, u)) (N (t, s, u)) -> (t, s, u) -> (t, s, u) #

(Additive v, Num n) => Transformable (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Methods

transform :: Transformation (V (Query v n m)) (N (Query v n m)) -> Query v n m -> Query v n m #

Transformable (Prim b v n) #

The Transformable instance for Prim just pushes calls to transform down through the Prim constructor.

Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (Prim b v n)) (N (Prim b v n)) -> Prim b v n -> Prim b v n #

Transformable (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (SubMap b v n m)) (N (SubMap b v n m)) -> SubMap b v n m -> SubMap b v n m #

Transformable (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) -> Subdiagram b v n m -> Subdiagram b v n m #

(OrderedField n, Metric v, Semigroup m) => Transformable (QDiagram b v n m) #

Diagrams can be transformed by transforming each of their components appropriately.

Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m #

Translational invariance

newtype TransInv t #

TransInv is a wrapper which makes a transformable type translationally invariant; the translational component of transformations will no longer affect things wrapped in TransInv.

Constructors

TransInv t 
Instances
Eq t => Eq (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

(==) :: TransInv t -> TransInv t -> Bool #

(/=) :: TransInv t -> TransInv t -> Bool #

Ord t => Ord (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

compare :: TransInv t -> TransInv t -> Ordering #

(<) :: TransInv t -> TransInv t -> Bool #

(<=) :: TransInv t -> TransInv t -> Bool #

(>) :: TransInv t -> TransInv t -> Bool #

(>=) :: TransInv t -> TransInv t -> Bool #

max :: TransInv t -> TransInv t -> TransInv t #

min :: TransInv t -> TransInv t -> TransInv t #

Show t => Show (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

showsPrec :: Int -> TransInv t -> ShowS #

show :: TransInv t -> String #

showList :: [TransInv t] -> ShowS #

Semigroup t => Semigroup (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

(<>) :: TransInv t -> TransInv t -> TransInv t #

sconcat :: NonEmpty (TransInv t) -> TransInv t #

stimes :: Integral b => b -> TransInv t -> TransInv t #

Monoid t => Monoid (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

mempty :: TransInv t #

mappend :: TransInv t -> TransInv t -> TransInv t #

mconcat :: [TransInv t] -> TransInv t #

Wrapped (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Associated Types

type Unwrapped (TransInv t) :: Type #

HasOrigin (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

moveOriginTo :: Point (V (TransInv t)) (N (TransInv t)) -> TransInv t -> TransInv t #

(Num (N t), Additive (V t), Transformable t) => Transformable (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (TransInv t)) (N (TransInv t)) -> TransInv t -> TransInv t #

Qualifiable a => Qualifiable (TransInv a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> TransInv a -> TransInv a #

Traced t => Traced (TransInv t) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: TransInv t -> Trace (V (TransInv t)) (N (TransInv t)) #

Enveloped t => Enveloped (TransInv t) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: TransInv t -> Envelope (V (TransInv t)) (N (TransInv t)) #

Rewrapped (TransInv t) (TransInv t') # 
Instance details

Defined in Diagrams.Core.Transform

type Unwrapped (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

type Unwrapped (TransInv t) = t
type N (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

type N (TransInv t) = N t
type V (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

type V (TransInv t) = V t

eye :: (HasBasis v, Num n) => v (v n) #

Identity matrix.

Names

data AName #

Atomic names. AName is just an existential wrapper around things which are Typeable, Ord and Show.

Instances
Eq AName # 
Instance details

Defined in Diagrams.Core.Names

Methods

(==) :: AName -> AName -> Bool #

(/=) :: AName -> AName -> Bool #

Ord AName # 
Instance details

Defined in Diagrams.Core.Names

Methods

compare :: AName -> AName -> Ordering #

(<) :: AName -> AName -> Bool #

(<=) :: AName -> AName -> Bool #

(>) :: AName -> AName -> Bool #

(>=) :: AName -> AName -> Bool #

max :: AName -> AName -> AName #

min :: AName -> AName -> AName #

Show AName # 
Instance details

Defined in Diagrams.Core.Names

Methods

showsPrec :: Int -> AName -> ShowS #

show :: AName -> String #

showList :: [AName] -> ShowS #

IsName AName # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: AName -> Name #

Each Name Name AName AName # 
Instance details

Defined in Diagrams.Core.Names

data Name #

A (qualified) name is a (possibly empty) sequence of atomic names.

Instances
Eq Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Semigroup Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

(<>) :: Name -> Name -> Name #

sconcat :: NonEmpty Name -> Name #

stimes :: Integral b => b -> Name -> Name #

Monoid Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

mempty :: Name #

mappend :: Name -> Name -> Name #

mconcat :: [Name] -> Name #

Wrapped Name # 
Instance details

Defined in Diagrams.Core.Names

Associated Types

type Unwrapped Name :: Type #

Qualifiable Name #

Of course, names can be qualified using (.>).

Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a => a -> Name -> Name #

IsName Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Name -> Name #

Rewrapped Name Name # 
Instance details

Defined in Diagrams.Core.Names

Each Name Name AName AName # 
Instance details

Defined in Diagrams.Core.Names

Action Name a => Action Name (Deletable a) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Deletable a -> Deletable a #

Action Name (Trace v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Trace v n -> Trace v n #

Action Name (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Envelope v n -> Envelope v n #

Action Name (Query v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Query v n m -> Query v n m #

Action Name (SubMap b v n m) #

A name acts on a name map by qualifying every name in it.

Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> SubMap b v n m -> SubMap b v n m #

type Unwrapped Name # 
Instance details

Defined in Diagrams.Core.Names

class (Typeable a, Ord a, Show a) => IsName a where #

Class for those types which can be used as names. They must support Typeable (to facilitate extracting them from existential wrappers), Ord (for comparison and efficient storage) and Show.

To make an instance of IsName, you need not define any methods, just declare it.

WARNING: it is not recommended to use GeneralizedNewtypeDeriving in conjunction with IsName, since in that case the underlying type and the newtype will be considered equivalent when comparing names. For example:

    newtype WordN = WordN Int deriving (Show, Ord, Eq, Typeable, IsName)
  

is unlikely to work as intended, since (1 :: Int) and (WordN 1) will be considered equal as names. Instead, use

    newtype WordN = WordN Int deriving (Show, Ord, Eq, Typeable, IsName)
    instance IsName WordN
  

Minimal complete definition

Nothing

Methods

toName :: a -> Name #

Instances
IsName Bool # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Bool -> Name #

IsName Char # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Char -> Name #

IsName Double # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Double -> Name #

IsName Float # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Float -> Name #

IsName Int # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Int -> Name #

IsName Integer # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Integer -> Name #

IsName () # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: () -> Name #

IsName Name # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Name -> Name #

IsName AName # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: AName -> Name #

IsName a => IsName [a] # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: [a] -> Name #

IsName a => IsName (Maybe a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: Maybe a -> Name #

(IsName a, IsName b) => IsName (a, b) # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: (a, b) -> Name #

(IsName a, IsName b, IsName c) => IsName (a, b, c) # 
Instance details

Defined in Diagrams.Core.Names

Methods

toName :: (a, b, c) -> Name #

class Qualifiable q where #

Instances of Qualifiable are things which can be qualified by prefixing them with a name.

Methods

(.>>) :: IsName a => a -> q -> q infixr 5 #

Qualify with the given name.

Instances
Qualifiable Name #

Of course, names can be qualified using (.>).

Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a => a -> Name -> Name #

Qualifiable a => Qualifiable [a] # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> [a] -> [a] #

(Ord a, Qualifiable a) => Qualifiable (Set a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> Set a -> Set a #

Qualifiable a => Qualifiable (TransInv a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> TransInv a -> TransInv a #

Qualifiable a => Qualifiable (b -> a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> (b -> a) -> b -> a #

(Qualifiable a, Qualifiable b) => Qualifiable (a, b) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> (a, b) -> (a, b) #

Qualifiable a => Qualifiable (Map k a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> Map k a -> Map k a #

Qualifiable a => Qualifiable (Measured n a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> Measured n a -> Measured n a #

(Qualifiable a, Qualifiable b, Qualifiable c) => Qualifiable (a, b, c) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> (a, b, c) -> (a, b, c) #

Qualifiable (SubMap b v n m) #

SubMaps are qualifiable: if ns is a SubMap, then a |> ns is the same SubMap except with every name qualified by a.

Instance details

Defined in Diagrams.Core.Types

Methods

(.>>) :: IsName a => a -> SubMap b v n m -> SubMap b v n m #

(Metric v, OrderedField n, Semigroup m) => Qualifiable (QDiagram b v n m) #

Diagrams can be qualified so that all their named points can now be referred to using the qualification prefix.

Instance details

Defined in Diagrams.Core.Types

Methods

(.>>) :: IsName a => a -> QDiagram b v n m -> QDiagram b v n m #

(.>) :: (IsName a1, IsName a2) => a1 -> a2 -> Name infixr 5 #

Convenient operator for writing qualified names with atomic components of different types. Instead of writing toName a1 <> toName a2 <> toName a3 you can just write a1 .> a2 .> a3.

eachName :: (Typeable a, Ord a, Show a) => Traversal' Name a #

Traversal over each name in a Name that matches the target type.

>>> toListOf eachName (a .> False .> b) :: String
"ab"
>>> a .> True .> b & eachName %~ not
a .> False .> b

Note that the type of the name is very important.

>>> sumOf eachName ((1::Int) .> (2 :: Integer) .> (3 :: Int)) :: Int
4
>>> sumOf eachName ((1::Int) .> (2 :: Integer) .> (3 :: Int)) :: Integer
2

Subdiagram maps

newtype SubMap b v n m #

A SubMap is a map associating names to subdiagrams. There can be multiple associations for any given name.

Constructors

SubMap (Map Name [Subdiagram b v n m]) 
Instances
Action Name (SubMap b v n m) #

A name acts on a name map by qualifying every name in it.

Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> SubMap b v n m -> SubMap b v n m #

Functor (SubMap b v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

fmap :: (a -> b0) -> SubMap b v n a -> SubMap b v n b0 #

(<$) :: a -> SubMap b v n b0 -> SubMap b v n a #

Semigroup (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

(<>) :: SubMap b v n m -> SubMap b v n m -> SubMap b v n m #

sconcat :: NonEmpty (SubMap b v n m) -> SubMap b v n m #

stimes :: Integral b0 => b0 -> SubMap b v n m -> SubMap b v n m #

Monoid (SubMap b v n m) #

SubMaps form a monoid with the empty map as the identity, and map union as the binary operation. No information is ever lost: if two maps have the same name in their domain, the resulting map will associate that name to the concatenation of the information associated with that name.

Instance details

Defined in Diagrams.Core.Types

Methods

mempty :: SubMap b v n m #

mappend :: SubMap b v n m -> SubMap b v n m -> SubMap b v n m #

mconcat :: [SubMap b v n m] -> SubMap b v n m #

Wrapped (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Associated Types

type Unwrapped (SubMap b v n m) :: Type #

Methods

_Wrapped' :: Iso' (SubMap b v n m) (Unwrapped (SubMap b v n m)) #

(OrderedField n, Metric v) => HasOrigin (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

moveOriginTo :: Point (V (SubMap b v n m)) (N (SubMap b v n m)) -> SubMap b v n m -> SubMap b v n m #

Transformable (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (SubMap b v n m)) (N (SubMap b v n m)) -> SubMap b v n m -> SubMap b v n m #

Qualifiable (SubMap b v n m) #

SubMaps are qualifiable: if ns is a SubMap, then a |> ns is the same SubMap except with every name qualified by a.

Instance details

Defined in Diagrams.Core.Types

Methods

(.>>) :: IsName a => a -> SubMap b v n m -> SubMap b v n m #

Rewrapped (SubMap b v n m) (SubMap b' v' n' m') # 
Instance details

Defined in Diagrams.Core.Types

type Unwrapped (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type Unwrapped (SubMap b v n m) = Map Name [Subdiagram b v n m]
type N (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type N (SubMap b v n m) = n
type V (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type V (SubMap b v n m) = v

fromNames :: IsName a => [(a, Subdiagram b v n m)] -> SubMap b v n m #

Construct a SubMap from a list of associations between names and subdiagrams.

rememberAs :: IsName a => a -> QDiagram b v n m -> SubMap b v n m -> SubMap b v n m #

Add a name/diagram association to a submap.

lookupSub :: IsName nm => nm -> SubMap b v n m -> Maybe [Subdiagram b v n m] #

Look for the given name in a name map, returning a list of subdiagrams associated with that name. If no names match the given name exactly, return all the subdiagrams associated with names of which the given name is a suffix.

Attributes and styles

class (Typeable a, Semigroup a) => AttributeClass a #

Every attribute must be an instance of AttributeClass, which simply guarantees Typeable and Semigroup constraints. The Semigroup instance for an attribute determines how it will combine with other attributes of the same type.

data Attribute (v :: * -> *) n :: * where #

An existential wrapper type to hold attributes. Some attributes are simply inert/static; some are affected by transformations; and some are affected by transformations and can be modified generically.

Constructors

Attribute :: AttributeClass a => a -> Attribute v n 
MAttribute :: AttributeClass a => Measured n a -> Attribute v n 
TAttribute :: (AttributeClass a, Transformable a, V a ~ v, N a ~ n) => a -> Attribute v n 
Instances
Show (Attribute v n) #

Shows the kind of attribute and the type contained in the attribute.

Instance details

Defined in Diagrams.Core.Style

Methods

showsPrec :: Int -> Attribute v n -> ShowS #

show :: Attribute v n -> String #

showList :: [Attribute v n] -> ShowS #

Typeable n => Semigroup (Attribute v n) #

Attributes form a semigroup, where the semigroup operation simply returns the right-hand attribute when the types do not match, and otherwise uses the semigroup operation specific to the (matching) types.

Instance details

Defined in Diagrams.Core.Style

Methods

(<>) :: Attribute v n -> Attribute v n -> Attribute v n #

sconcat :: NonEmpty (Attribute v n) -> Attribute v n #

stimes :: Integral b => b -> Attribute v n -> Attribute v n #

(Additive v, Traversable v, Floating n) => Transformable (Attribute v n) #

TAttributes are transformed directly, MAttributes have their local scale multiplied by the average scale of the transform. Plain Attributes are unaffected.

Instance details

Defined in Diagrams.Core.Style

Methods

transform :: Transformation (V (Attribute v n)) (N (Attribute v n)) -> Attribute v n -> Attribute v n #

Each (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') # 
Instance details

Defined in Diagrams.Core.Style

Methods

each :: Traversal (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') #

type N (Attribute v n) # 
Instance details

Defined in Diagrams.Core.Style

type N (Attribute v n) = n
type V (Attribute v n) # 
Instance details

Defined in Diagrams.Core.Style

type V (Attribute v n) = v

data Style v n #

A Style is a heterogeneous collection of attributes, containing at most one attribute of any given type.

Instances
Show (Style v n) #

Show the attributes in the style.

Instance details

Defined in Diagrams.Core.Style

Methods

showsPrec :: Int -> Style v n -> ShowS #

show :: Style v n -> String #

showList :: [Style v n] -> ShowS #

Typeable n => Semigroup (Style v n) #

Combine a style by combining the attributes; if the two styles have attributes of the same type they are combined according to their semigroup structure.

Instance details

Defined in Diagrams.Core.Style

Methods

(<>) :: Style v n -> Style v n -> Style v n #

sconcat :: NonEmpty (Style v n) -> Style v n #

stimes :: Integral b => b -> Style v n -> Style v n #

Typeable n => Monoid (Style v n) #

The empty style contains no attributes.

Instance details

Defined in Diagrams.Core.Style

Methods

mempty :: Style v n #

mappend :: Style v n -> Style v n -> Style v n #

mconcat :: [Style v n] -> Style v n #

Ixed (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Methods

ix :: Index (Style v n) -> Traversal' (Style v n) (IxValue (Style v n)) #

At (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Methods

at :: Index (Style v n) -> Lens' (Style v n) (Maybe (IxValue (Style v n))) #

Wrapped (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Associated Types

type Unwrapped (Style v n) :: Type #

Methods

_Wrapped' :: Iso' (Style v n) (Unwrapped (Style v n)) #

(Additive v, Traversable v, Floating n) => Transformable (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Methods

transform :: Transformation (V (Style v n)) (N (Style v n)) -> Style v n -> Style v n #

Typeable n => HasStyle (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (Style v n)) (N (Style v n)) -> Style v n -> Style v n #

Action (Style v n) m #

Styles have no action on other monoids.

Instance details

Defined in Diagrams.Core.Style

Methods

act :: Style v n -> m -> m #

Rewrapped (Style v n) (Style v' n') # 
Instance details

Defined in Diagrams.Core.Style

Each (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') # 
Instance details

Defined in Diagrams.Core.Style

Methods

each :: Traversal (Style v n) (Style v' n') (Attribute v n) (Attribute v' n') #

type Index (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type Index (Style v n) = TypeRep
type IxValue (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type IxValue (Style v n) = Attribute v n
type Unwrapped (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type N (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type N (Style v n) = n
type V (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

type V (Style v n) = v

class HasStyle a where #

Type class for things which have a style.

Methods

applyStyle :: Style (V a) (N a) -> a -> a #

Apply a style by combining it (on the left) with the existing style.

Instances
HasStyle a => HasStyle [a] # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V [a]) (N [a]) -> [a] -> [a] #

(HasStyle a, Ord a) => HasStyle (Set a) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (Set a)) (N (Set a)) -> Set a -> Set a #

HasStyle b => HasStyle (a -> b) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (a -> b)) (N (a -> b)) -> (a -> b) -> a -> b #

(HasStyle a, HasStyle b, V a ~ V b, N a ~ N b) => HasStyle (a, b) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (a, b)) (N (a, b)) -> (a, b) -> (a, b) #

HasStyle a => HasStyle (Map k a) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (Map k a)) (N (Map k a)) -> Map k a -> Map k a #

HasStyle b => HasStyle (Measured n b) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (Measured n b)) (N (Measured n b)) -> Measured n b -> Measured n b #

Typeable n => HasStyle (Style v n) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (Style v n)) (N (Style v n)) -> Style v n -> Style v n #

(Metric v, OrderedField n, Semigroup m) => HasStyle (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

applyStyle :: Style (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m #

getAttr :: forall a v n. AttributeClass a => Style v n -> Maybe a #

Extract an attribute from a style of a particular type. If the style contains an attribute of the requested type, it will be returned wrapped in Just; otherwise, Nothing is returned.

Trying to extract a measured attibute will fail. It either has to be unmeasured with unmeasureAttrs or use the atMAttr lens.

atAttr :: AttributeClass a => Lens' (Style v n) (Maybe a) #

Lens onto a plain attribute of a style.

atMAttr :: (AttributeClass a, Typeable n) => Lens' (Style v n) (Maybe (Measured n a)) #

Lens onto a measured attribute of a style.

atTAttr :: (V a ~ v, N a ~ n, AttributeClass a, Transformable a) => Lens' (Style v n) (Maybe a) #

Lens onto a transformable attribute of a style.

applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d #

Apply an attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

applyMAttr :: (AttributeClass a, N d ~ n, HasStyle d) => Measured n a -> d -> d #

Apply a measured attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, N a ~ N d, HasStyle d) => a -> d -> d #

Apply a transformable attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

Envelopes

newtype Envelope v n #

Every diagram comes equipped with an envelope. What is an envelope?

Consider first the idea of a bounding box. A bounding box expresses the distance to a bounding plane in every direction parallel to an axis. That is, a bounding box can be thought of as the intersection of a collection of half-planes, two perpendicular to each axis.

More generally, the intersection of half-planes in every direction would give a tight "bounding region", or convex hull. However, representing such a thing intensionally would be impossible; hence bounding boxes are often used as an approximation.

An envelope is an extensional representation of such a "bounding region". Instead of storing some sort of direct representation, we store a function which takes a direction as input and gives a distance to a bounding half-plane as output. The important point is that envelopes can be composed, and transformed by any affine transformation.

Formally, given a vector v, the envelope computes a scalar s such that

  • for every point u inside the diagram, if the projection of (u - origin) onto v is s' *^ v, then s' <= s.
  • s is the smallest such scalar.

There is also a special "empty envelope".

The idea for envelopes came from Sebastian Setzer; see http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030. See also Brent Yorgey, Monoids: Theme and Variations, published in the 2012 Haskell Symposium: http://ozark.hendrix.edu/~yorgey/pub/monoid-pearl.pdf; video: http://www.youtube.com/watch?v=X-8NCkD2vOw.

Constructors

Envelope (Option (v n -> Max n)) 
Instances
Action Name (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Envelope v n -> Envelope v n #

Show (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

showsPrec :: Int -> Envelope v n -> ShowS #

show :: Envelope v n -> String #

showList :: [Envelope v n] -> ShowS #

Ord n => Semigroup (Envelope v n) #

Envelopes form a semigroup with pointwise maximum as composition. Hence, if e1 is the envelope for diagram d1, and e2 is the envelope for d2, then e1 `mappend` e2 is the envelope for d1 `atop` d2.

Instance details

Defined in Diagrams.Core.Envelope

Methods

(<>) :: Envelope v n -> Envelope v n -> Envelope v n #

sconcat :: NonEmpty (Envelope v n) -> Envelope v n #

stimes :: Integral b => b -> Envelope v n -> Envelope v n #

Ord n => Monoid (Envelope v n) #

The special empty envelope is the identity for the Monoid instance.

Instance details

Defined in Diagrams.Core.Envelope

Methods

mempty :: Envelope v n #

mappend :: Envelope v n -> Envelope v n -> Envelope v n #

mconcat :: [Envelope v n] -> Envelope v n #

Wrapped (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Associated Types

type Unwrapped (Envelope v n) :: Type #

Methods

_Wrapped' :: Iso' (Envelope v n) (Unwrapped (Envelope v n)) #

(Metric v, Fractional n) => HasOrigin (Envelope v n) #

The local origin of an envelope is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate.

Instance details

Defined in Diagrams.Core.Envelope

Methods

moveOriginTo :: Point (V (Envelope v n)) (N (Envelope v n)) -> Envelope v n -> Envelope v n #

(Metric v, Floating n) => Transformable (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

transform :: Transformation (V (Envelope v n)) (N (Envelope v n)) -> Envelope v n -> Envelope v n #

(Metric v, OrderedField n) => Enveloped (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: Envelope v n -> Envelope (V (Envelope v n)) (N (Envelope v n)) #

(Metric v, OrderedField n) => Juxtaposable (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (Envelope v n) -> Envelope v n -> Envelope v n -> Envelope v n #

Rewrapped (Envelope v n) (Envelope v' n') # 
Instance details

Defined in Diagrams.Core.Envelope

type Unwrapped (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

type Unwrapped (Envelope v n) = Option (v n -> Max n)
type N (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

type N (Envelope v n) = n
type V (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

type V (Envelope v n) = v

appEnvelope :: Envelope v n -> Maybe (v n -> n) #

"Apply" an envelope by turning it into a function. Nothing is returned iff the envelope is empty.

onEnvelope :: ((v n -> n) -> v n -> n) -> Envelope v n -> Envelope v n #

A convenient way to transform an envelope, by specifying a transformation on the underlying v n -> n function. The empty envelope is unaffected.

mkEnvelope :: (v n -> n) -> Envelope v n #

Create an envelope from a v n -> n function.

class (Metric (V a), OrderedField (N a)) => Enveloped a where #

Enveloped abstracts over things which have an envelope.

Methods

getEnvelope :: a -> Envelope (V a) (N a) #

Compute the envelope of an object. For types with an intrinsic notion of "local origin", the envelope will be based there. Other types (e.g. Trail) may have some other default reference point at which the envelope will be based; their instances should document what it is.

Instances
Enveloped b => Enveloped [b] # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: [b] -> Envelope (V [b]) (N [b]) #

Enveloped b => Enveloped (Set b) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: Set b -> Envelope (V (Set b)) (N (Set b)) #

Enveloped t => Enveloped (TransInv t) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: TransInv t -> Envelope (V (TransInv t)) (N (TransInv t)) #

(Enveloped a, Enveloped b, V a ~ V b, N a ~ N b) => Enveloped (a, b) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: (a, b) -> Envelope (V (a, b)) (N (a, b)) #

Enveloped b => Enveloped (Map k b) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: Map k b -> Envelope (V (Map k b)) (N (Map k b)) #

(OrderedField n, Metric v) => Enveloped (Point v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: Point v n -> Envelope (V (Point v n)) (N (Point v n)) #

(Metric v, OrderedField n) => Enveloped (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Envelope

Methods

getEnvelope :: Envelope v n -> Envelope (V (Envelope v n)) (N (Envelope v n)) #

(OrderedField n, Metric v, Monoid' m) => Enveloped (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getEnvelope :: Subdiagram b v n m -> Envelope (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) #

(Metric v, OrderedField n, Monoid' m) => Enveloped (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getEnvelope :: QDiagram b v n m -> Envelope (V (QDiagram b v n m)) (N (QDiagram b v n m)) #

envelopeVMay :: Enveloped a => Vn a -> a -> Maybe (Vn a) #

Compute the vector from the local origin to a separating hyperplane in the given direction, or Nothing for the empty envelope.

envelopeV :: Enveloped a => Vn a -> a -> Vn a #

Compute the vector from the local origin to a separating hyperplane in the given direction. Returns the zero vector for the empty envelope.

envelopePMay :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Maybe (Point v n) #

Compute the point on a separating hyperplane in the given direction, or Nothing for the empty envelope.

envelopeP :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> Point v n #

Compute the point on a separating hyperplane in the given direction. Returns the origin for the empty envelope.

diameter :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n #

Compute the diameter of a enveloped object along a particular vector. Returns zero for the empty envelope.

radius :: (V a ~ v, N a ~ n, Enveloped a) => v n -> a -> n #

Compute the "radius" (1/2 the diameter) of an enveloped object along a particular vector.

size :: (V a ~ v, N a ~ n, Enveloped a, HasBasis v) => a -> v n #

The smallest positive axis-parallel vector that bounds the envelope of an object.

Traces

newtype Trace v n #

Every diagram comes equipped with a trace. Intuitively, the trace for a diagram is like a raytracer: given a line (represented as a base point and a direction vector), the trace computes a sorted list of signed distances from the base point to all intersections of the line with the boundary of the diagram.

Note that the outputs are not absolute distances, but multipliers relative to the input vector. That is, if the base point is p and direction vector is v, and one of the output scalars is s, then there is an intersection at the point p .+^ (s *^ v).

Constructors

Trace (Point v n -> v n -> SortedList n) 
Instances
Action Name (Trace v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Trace v n -> Trace v n #

Show (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

showsPrec :: Int -> Trace v n -> ShowS #

show :: Trace v n -> String #

showList :: [Trace v n] -> ShowS #

Ord n => Semigroup (Trace v n) #

Traces form a semigroup with pointwise minimum as composition. Hence, if t1 is the trace for diagram d1, and e2 is the trace for d2, then e1 `mappend` e2 is the trace for d1 `atop` d2.

Instance details

Defined in Diagrams.Core.Trace

Methods

(<>) :: Trace v n -> Trace v n -> Trace v n #

sconcat :: NonEmpty (Trace v n) -> Trace v n #

stimes :: Integral b => b -> Trace v n -> Trace v n #

Ord n => Monoid (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

mempty :: Trace v n #

mappend :: Trace v n -> Trace v n -> Trace v n #

mconcat :: [Trace v n] -> Trace v n #

Wrapped (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Associated Types

type Unwrapped (Trace v n) :: Type #

Methods

_Wrapped' :: Iso' (Trace v n) (Unwrapped (Trace v n)) #

(Additive v, Num n) => HasOrigin (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

moveOriginTo :: Point (V (Trace v n)) (N (Trace v n)) -> Trace v n -> Trace v n #

(Additive v, Num n) => Transformable (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

transform :: Transformation (V (Trace v n)) (N (Trace v n)) -> Trace v n -> Trace v n #

(Additive v, Ord n) => Traced (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: Trace v n -> Trace (V (Trace v n)) (N (Trace v n)) #

Rewrapped (Trace v n) (Trace v' n') # 
Instance details

Defined in Diagrams.Core.Trace

type Unwrapped (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

type Unwrapped (Trace v n) = Point v n -> v n -> SortedList n
type N (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

type N (Trace v n) = n
type V (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

type V (Trace v n) = v

data SortedList a #

A newtype wrapper around a list which maintains the invariant that the list is sorted. The constructor is not exported; use the smart constructor mkSortedList (which sorts the given list) instead.

Instances
Ord a => Semigroup (SortedList a) #

SortedList forms a semigroup with merge as composition.

Instance details

Defined in Diagrams.Core.Trace

Ord a => Monoid (SortedList a) #

SortedList forms a monoid with merge and the empty list.

Instance details

Defined in Diagrams.Core.Trace

mkSortedList :: Ord a => [a] -> SortedList a #

A smart constructor for the SortedList type, which sorts the input to ensure the SortedList invariant.

getSortedList :: SortedList a -> [a] #

Project the (guaranteed sorted) list out of a SortedList wrapper.

appTrace :: Trace v n -> Point v n -> v n -> SortedList n #

mkTrace :: (Point v n -> v n -> SortedList n) -> Trace v n #

class (Additive (V a), Ord (N a)) => Traced a where #

Traced abstracts over things which have a trace.

Methods

getTrace :: a -> Trace (V a) (N a) #

Compute the trace of an object.

Instances
Traced b => Traced [b] # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: [b] -> Trace (V [b]) (N [b]) #

Traced b => Traced (Set b) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: Set b -> Trace (V (Set b)) (N (Set b)) #

Traced t => Traced (TransInv t) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: TransInv t -> Trace (V (TransInv t)) (N (TransInv t)) #

(Traced a, Traced b, SameSpace a b) => Traced (a, b) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: (a, b) -> Trace (V (a, b)) (N (a, b)) #

Traced b => Traced (Map k b) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: Map k b -> Trace (V (Map k b)) (N (Map k b)) #

(Additive v, Ord n) => Traced (Point v n) #

The trace of a single point is the empty trace, i.e. the one which returns no intersection points for every query. Arguably it should return a single finite distance for vectors aimed directly at the given point, but due to floating-point inaccuracy this is problematic. Note that the envelope for a single point is not the empty envelope (see Diagrams.Core.Envelope).

Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: Point v n -> Trace (V (Point v n)) (N (Point v n)) #

(Additive v, Ord n) => Traced (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

getTrace :: Trace v n -> Trace (V (Trace v n)) (N (Trace v n)) #

(OrderedField n, Metric v, Semigroup m) => Traced (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getTrace :: Subdiagram b v n m -> Trace (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) #

(Metric v, OrderedField n, Semigroup m) => Traced (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getTrace :: QDiagram b v n m -> Trace (V (QDiagram b v n m)) (N (QDiagram b v n m)) #

traceV :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (V a n) #

Compute the vector from the given point p to the "smallest" boundary intersection along the given vector v. The "smallest" boundary intersection is defined as the one given by p .+^ (s *^ v) for the smallest (most negative) value of s. Return Nothing if there is no intersection. See also traceP.

See also rayTraceV which uses the smallest positive intersection, which is often more intuitive behavior.

traceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #

Compute the "smallest" boundary point along the line determined by the given point p and vector v. The "smallest" boundary point is defined as the one given by p .+^ (s *^ v) for the smallest (most negative) value of s. Return Nothing if there is no such boundary point. See also traceV.

See also rayTraceP which uses the smallest positive intersection, which is often more intuitive behavior.

maxTraceV :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (V a n) #

Like traceV, but computes a vector to the "largest" boundary point instead of the smallest. (Note, however, the "largest" boundary point may still be in the opposite direction from the given vector, if all the boundary points are, as in the third example shown below.)

maxTraceP :: (n ~ N a, Num n, Traced a) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #

Like traceP, but computes the "largest" boundary point instead of the smallest. (Note, however, the "largest" boundary point may still be in the opposite direction from the given vector, if all the boundary points are.)

rayTraceV :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (V a n) #

Compute the vector from the given point to the closest boundary point of the given object in the given direction, or Nothing if there is no such boundary point (as in the third example below). Note that unlike traceV, only positive boundary points are considered, i.e. boundary points corresponding to a positive scalar multiple of the direction vector. This is intuitively the "usual" behavior of a raytracer, which only considers intersections "in front of" the camera. Compare the second example diagram below with the second example shown for traceV.

rayTraceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #

Compute the boundary point on an object which is closest to the given base point in the given direction, or Nothing if there is no such boundary point. Note that unlike traceP, only positive boundary points are considered, i.e. boundary points corresponding to a positive scalar multiple of the direction vector. This is intuitively the "usual" behavior of a raytracer, which only considers intersection points "in front of" the camera.

maxRayTraceV :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (V a n) #

Like rayTraceV, but computes a vector to the "largest" boundary point instead of the smallest. Considers only positive boundary points.

maxRayTraceP :: (n ~ N a, Traced a, Num n) => Point (V a) n -> V a n -> a -> Maybe (Point (V a) n) #

Like rayTraceP, but computes the "largest" boundary point instead of the smallest. Considers only positive boundary points.

Things with local origins

class HasOrigin t where #

Class of types which have an intrinsic notion of a "local origin", i.e. things which are not invariant under translation, and which allow the origin to be moved.

One might wonder why not just use Transformable instead of having a separate class for HasOrigin; indeed, for types which are instances of both we should have the identity

  moveOriginTo (origin .^+ v) === translate (negated v)
  

The reason is that some things (e.g. vectors, Trails) are transformable but are translationally invariant, i.e. have no origin.

Methods

moveOriginTo :: Point (V t) (N t) -> t -> t #

Move the local origin to another point.

Note that this function is in some sense dual to translate (for types which are also Transformable); moving the origin itself while leaving the object "fixed" is dual to fixing the origin and translating the diagram.

Instances
HasOrigin t => HasOrigin [t] # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V [t]) (N [t]) -> [t] -> [t] #

(HasOrigin t, Ord t) => HasOrigin (Set t) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (Set t)) (N (Set t)) -> Set t -> Set t #

HasOrigin (TransInv t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

moveOriginTo :: Point (V (TransInv t)) (N (TransInv t)) -> TransInv t -> TransInv t #

(HasOrigin t, HasOrigin s, SameSpace s t) => HasOrigin (s, t) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (s, t)) (N (s, t)) -> (s, t) -> (s, t) #

HasOrigin t => HasOrigin (Map k t) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (Map k t)) (N (Map k t)) -> Map k t -> Map k t #

(Additive v, Num n) => HasOrigin (Point v n) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (Point v n)) (N (Point v n)) -> Point v n -> Point v n #

HasOrigin t => HasOrigin (Measured n t) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (Measured n t)) (N (Measured n t)) -> Measured n t -> Measured n t #

(Additive v, Num n) => HasOrigin (Transformation v n) # 
Instance details

Defined in Diagrams.Core.Transform

(Additive v, Num n) => HasOrigin (Trace v n) # 
Instance details

Defined in Diagrams.Core.Trace

Methods

moveOriginTo :: Point (V (Trace v n)) (N (Trace v n)) -> Trace v n -> Trace v n #

(Metric v, Fractional n) => HasOrigin (Envelope v n) #

The local origin of an envelope is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate.

Instance details

Defined in Diagrams.Core.Envelope

Methods

moveOriginTo :: Point (V (Envelope v n)) (N (Envelope v n)) -> Envelope v n -> Envelope v n #

(Additive v, Num n) => HasOrigin (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Methods

moveOriginTo :: Point (V (Query v n m)) (N (Query v n m)) -> Query v n m -> Query v n m #

(OrderedField n, Metric v) => HasOrigin (SubMap b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

moveOriginTo :: Point (V (SubMap b v n m)) (N (SubMap b v n m)) -> SubMap b v n m -> SubMap b v n m #

(Metric v, OrderedField n) => HasOrigin (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

moveOriginTo :: Point (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) -> Subdiagram b v n m -> Subdiagram b v n m #

(Metric v, OrderedField n, Semigroup m) => HasOrigin (QDiagram b v n m) #

Every diagram has an intrinsic "local origin" which is the basis for all combining operations.

Instance details

Defined in Diagrams.Core.Types

Methods

moveOriginTo :: Point (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m #

moveOriginBy :: (V t ~ v, N t ~ n, HasOrigin t) => v n -> t -> t #

Move the local origin by a relative vector.

Juxtaposable things

class Juxtaposable a where #

Class of things which can be placed "next to" other things, for some appropriate notion of "next to".

Methods

juxtapose :: Vn a -> a -> a -> a #

juxtapose v a1 a2 positions a2 next to a1 in the direction of v. In particular, place a2 so that v points from the local origin of a1 towards the old local origin of a2; a1's local origin becomes a2's new local origin. The result is just a translated version of a2. (In particular, this operation does not combine a1 and a2 in any way.)

Instances
(Enveloped b, HasOrigin b) => Juxtaposable [b] # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn [b] -> [b] -> [b] -> [b] #

(Enveloped b, HasOrigin b, Ord b) => Juxtaposable (Set b) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (Set b) -> Set b -> Set b -> Set b #

Juxtaposable a => Juxtaposable (b -> a) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (b -> a) -> (b -> a) -> (b -> a) -> b -> a #

(Enveloped a, HasOrigin a, Enveloped b, HasOrigin b, V a ~ V b, N a ~ N b) => Juxtaposable (a, b) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (a, b) -> (a, b) -> (a, b) -> (a, b) #

(Enveloped b, HasOrigin b) => Juxtaposable (Map k b) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (Map k b) -> Map k b -> Map k b -> Map k b #

Juxtaposable a => Juxtaposable (Measured n a) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (Measured n a) -> Measured n a -> Measured n a -> Measured n a #

(Metric v, OrderedField n) => Juxtaposable (Envelope v n) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (Envelope v n) -> Envelope v n -> Envelope v n -> Envelope v n #

(Metric v, OrderedField n, Monoid' m) => Juxtaposable (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

juxtapose :: Vn (QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m #

juxtaposeDefault :: (Enveloped a, HasOrigin a) => Vn a -> a -> a -> a #

Default implementation of juxtapose for things which are instances of Enveloped and HasOrigin. If either envelope is empty, the second object is returned unchanged.

Queries

newtype Query v n m #

A query is a function that maps points in a vector space to values in some monoid. Queries naturally form a monoid, with two queries being combined pointwise.

The idea for annotating diagrams with monoidal queries came from the graphics-drawingcombinators package, http://hackage.haskell.org/package/graphics-drawingcombinators.

Constructors

Query 

Fields

Instances
Action Name (Query v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

act :: Name -> Query v n m -> Query v n m #

Functor v => Profunctor (Query v) # 
Instance details

Defined in Diagrams.Core.Query

Methods

dimap :: (a -> b) -> (c -> d) -> Query v b c -> Query v a d #

lmap :: (a -> b) -> Query v b c -> Query v a c #

rmap :: (b -> c) -> Query v a b -> Query v a c #

(#.) :: Coercible c b => q b c -> Query v a b -> Query v a c #

(.#) :: Coercible b a => Query v b c -> q a b -> Query v a c #

Functor v => Corepresentable (Query v) # 
Instance details

Defined in Diagrams.Core.Query

Associated Types

type Corep (Query v) :: Type -> Type #

Methods

cotabulate :: (Corep (Query v) d -> c) -> Query v d c #

Functor v => Closed (Query v) # 
Instance details

Defined in Diagrams.Core.Query

Methods

closed :: Query v a b -> Query v (x -> a) (x -> b) #

Functor v => Costrong (Query v) # 
Instance details

Defined in Diagrams.Core.Query

Methods

unfirst :: Query v (a, d) (b, d) -> Query v a b #

unsecond :: Query v (d, a) (d, b) -> Query v a b #

Functor v => Cosieve (Query v) (Point v) # 
Instance details

Defined in Diagrams.Core.Query

Methods

cosieve :: Query v a b -> Point v a -> b #

Monad (Query v n) # 
Instance details

Defined in Diagrams.Core.Query

Methods

(>>=) :: Query v n a -> (a -> Query v n b) -> Query v n b #

(>>) :: Query v n a -> Query v n b -> Query v n b #

return :: a -> Query v n a #

fail :: String -> Query v n a #

Functor (Query v n) # 
Instance details

Defined in Diagrams.Core.Query

Methods

fmap :: (a -> b) -> Query v n a -> Query v n b #

(<$) :: a -> Query v n b -> Query v n a #

Applicative (Query v n) # 
Instance details

Defined in Diagrams.Core.Query

Methods

pure :: a -> Query v n a #

(<*>) :: Query v n (a -> b) -> Query v n a -> Query v n b #

liftA2 :: (a -> b -> c) -> Query v n a -> Query v n b -> Query v n c #

(*>) :: Query v n a -> Query v n b -> Query v n b #

(<*) :: Query v n a -> Query v n b -> Query v n a #

Distributive (Query v n) # 
Instance details

Defined in Diagrams.Core.Query

Methods

distribute :: Functor f => f (Query v n a) -> Query v n (f a) #

collect :: Functor f => (a -> Query v n b) -> f a -> Query v n (f b) #

distributeM :: Monad m => m (Query v n a) -> Query v n (m a) #

collectM :: Monad m => (a -> Query v n b) -> m a -> Query v n (m b) #

Representable (Query v n) # 
Instance details

Defined in Diagrams.Core.Query

Associated Types

type Rep (Query v n) :: Type #

Methods

tabulate :: (Rep (Query v n) -> a) -> Query v n a #

index :: Query v n a -> Rep (Query v n) -> a #

Semigroup m => Semigroup (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Methods

(<>) :: Query v n m -> Query v n m -> Query v n m #

sconcat :: NonEmpty (Query v n m) -> Query v n m #

stimes :: Integral b => b -> Query v n m -> Query v n m #

Monoid m => Monoid (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Methods

mempty :: Query v n m #

mappend :: Query v n m -> Query v n m -> Query v n m #

mconcat :: [Query v n m] -> Query v n m #

Wrapped (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Associated Types

type Unwrapped (Query v n m) :: Type #

Methods

_Wrapped' :: Iso' (Query v n m) (Unwrapped (Query v n m)) #

(Additive v, Num n) => HasOrigin (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Methods

moveOriginTo :: Point (V (Query v n m)) (N (Query v n m)) -> Query v n m -> Query v n m #

(Additive v, Num n) => Transformable (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

Methods

transform :: Transformation (V (Query v n m)) (N (Query v n m)) -> Query v n m -> Query v n m #

Rewrapped (Query v a m) (Query v' a' m') # 
Instance details

Defined in Diagrams.Core.Query

type Corep (Query v) # 
Instance details

Defined in Diagrams.Core.Query

type Corep (Query v) = Point v
type Rep (Query v n) # 
Instance details

Defined in Diagrams.Core.Query

type Rep (Query v n) = Point v n
type Unwrapped (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

type Unwrapped (Query v n m) = Point v n -> m
type N (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

type N (Query v n m) = n
type V (Query v n m) # 
Instance details

Defined in Diagrams.Core.Query

type V (Query v n m) = v

Primitives

data Prim b v n where #

A value of type Prim b v n is an opaque (existentially quantified) primitive which backend b knows how to render in vector space v.

Constructors

Prim :: (Transformable p, Typeable p, Renderable p b) => p -> Prim b (V p) (N p) 
Instances
Transformable (Prim b v n) #

The Transformable instance for Prim just pushes calls to transform down through the Prim constructor.

Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (Prim b v n)) (N (Prim b v n)) -> Prim b v n -> Prim b v n #

Renderable (Prim b v n) b #

The Renderable instance for Prim just pushes calls to render down through the Prim constructor.

Instance details

Defined in Diagrams.Core.Types

Methods

render :: b -> Prim b v n -> Render b (V (Prim b v n)) (N (Prim b v n)) #

type N (Prim b v n) # 
Instance details

Defined in Diagrams.Core.Types

type N (Prim b v n) = n
type V (Prim b v n) # 
Instance details

Defined in Diagrams.Core.Types

type V (Prim b v n) = v

Diagrams

data QDiagram b v n m #

The fundamental diagram type. The type variables are as follows:

  • b represents the backend, such as SVG or Cairo. Note that each backend also exports a type synonym B for itself, so the type variable b may also typically be instantiated by B, meaning "use whatever backend is in scope".
  • v represents the vector space of the diagram. Typical instantiations include V2 (for a two-dimensional diagram) or V3 (for a three-dimensional diagram).
  • n represents the numerical field the diagram uses. Typically this will be a concrete numeric type like Double.
  • m is the monoidal type of "query annotations": each point in the diagram has a value of type m associated to it, and these values are combined according to the Monoid instance for m. Most often, m is simply instantiated to Any, associating a simple Bool value to each point indicating whether the point is inside the diagram; Diagram is a synonym for QDiagram with m thus instantiated to Any.

Diagrams can be combined via their Monoid instance, transformed via their Transformable instance, and assigned attributes via their HasStyle instance.

Note that the Q in QDiagram stands for "Queriable", as distinguished from Diagram, where m is fixed to Any. This is not really a very good name, but it's probably not worth changing it at this point.

Instances
Functor (QDiagram b v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

fmap :: (a -> b0) -> QDiagram b v n a -> QDiagram b v n b0 #

(<$) :: a -> QDiagram b v n b0 -> QDiagram b v n a #

(Metric v, OrderedField n, Semigroup m) => Semigroup (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

(<>) :: QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m #

sconcat :: NonEmpty (QDiagram b v n m) -> QDiagram b v n m #

stimes :: Integral b0 => b0 -> QDiagram b v n m -> QDiagram b v n m #

(Metric v, OrderedField n, Semigroup m) => Monoid (QDiagram b v n m) #

Diagrams form a monoid since each of their components do: the empty diagram has no primitives, an empty envelope, an empty trace, no named subdiagrams, and a constantly empty query function.

Diagrams compose by aligning their respective local origins. The new diagram has all the primitives and all the names from the two diagrams combined, and query functions are combined pointwise. The first diagram goes on top of the second. "On top of" probably only makes sense in vector spaces of dimension lower than 3, but in theory it could make sense for, say, 3-dimensional diagrams when viewed by 4-dimensional beings.

Instance details

Defined in Diagrams.Core.Types

Methods

mempty :: QDiagram b v n m #

mappend :: QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m #

mconcat :: [QDiagram b v n m] -> QDiagram b v n m #

Wrapped (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Associated Types

type Unwrapped (QDiagram b v n m) :: Type #

Methods

_Wrapped' :: Iso' (QDiagram b v n m) (Unwrapped (QDiagram b v n m)) #

(Metric v, OrderedField n, Semigroup m) => HasOrigin (QDiagram b v n m) #

Every diagram has an intrinsic "local origin" which is the basis for all combining operations.

Instance details

Defined in Diagrams.Core.Types

Methods

moveOriginTo :: Point (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m #

(OrderedField n, Metric v, Semigroup m) => Transformable (QDiagram b v n m) #

Diagrams can be transformed by transforming each of their components appropriately.

Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m #

(Metric v, OrderedField n, Semigroup m) => HasStyle (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

applyStyle :: Style (V (QDiagram b v n m)) (N (QDiagram b v n m)) -> QDiagram b v n m -> QDiagram b v n m #

(Metric v, OrderedField n, Semigroup m) => Qualifiable (QDiagram b v n m) #

Diagrams can be qualified so that all their named points can now be referred to using the qualification prefix.

Instance details

Defined in Diagrams.Core.Types

Methods

(.>>) :: IsName a => a -> QDiagram b v n m -> QDiagram b v n m #

(Metric v, OrderedField n, Semigroup m) => Traced (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getTrace :: QDiagram b v n m -> Trace (V (QDiagram b v n m)) (N (QDiagram b v n m)) #

(Metric v, OrderedField n, Monoid' m) => Enveloped (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getEnvelope :: QDiagram b v n m -> Envelope (V (QDiagram b v n m)) (N (QDiagram b v n m)) #

(Metric v, OrderedField n, Monoid' m) => Juxtaposable (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

juxtapose :: Vn (QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m #

Rewrapped (QDiagram b v n m) (QDiagram b' v' n' m') # 
Instance details

Defined in Diagrams.Core.Types

type Unwrapped (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type Unwrapped (QDiagram b v n m) = DUALTree (DownAnnots v n) (UpAnnots b v n m) Annotation (QDiaLeaf b v n m)
type N (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type N (QDiagram b v n m) = n
type V (QDiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type V (QDiagram b v n m) = v

type Diagram b = QDiagram b (V b) (N b) Any #

Diagram b is a synonym for QDiagram b (V b) (N b) Any. That is, the default sort of diagram is one where querying at a point simply tells you whether the diagram contains that point or not. Transforming a default diagram into one with a more interesting query can be done via the Functor instance of QDiagram b v n or the value function.

mkQD :: Prim b v n -> Envelope v n -> Trace v n -> SubMap b v n m -> Query v n m -> QDiagram b v n m #

Create a diagram from a single primitive, along with an envelope, trace, subdiagram map, and query function.

pointDiagram :: (Metric v, Fractional n) => Point v n -> QDiagram b v n m #

Create a "point diagram", which has no content, no trace, an empty query, and a point envelope.

envelope :: (OrderedField n, Metric v, Monoid' m) => Lens' (QDiagram b v n m) (Envelope v n) #

Lens onto the Envelope of a QDiagram.

trace :: (Metric v, OrderedField n, Semigroup m) => Lens' (QDiagram b v n m) (Trace v n) #

Lens onto the Trace of a QDiagram.

subMap :: (Metric v, Semigroup m, OrderedField n) => Lens' (QDiagram b v n m) (SubMap b v n m) #

Lens onto the SubMap of a QDiagram (i.e. an association from names to subdiagrams).

names :: (Metric v, Semigroup m, OrderedField n) => QDiagram b v n m -> [(Name, [Point v n])] #

Get a list of names of subdiagrams and their locations.

query :: Monoid m => QDiagram b v n m -> Query v n m #

Get the query function associated with a diagram.

nameSub :: (IsName nm, Metric v, OrderedField n, Semigroup m) => (QDiagram b v n m -> Subdiagram b v n m) -> nm -> QDiagram b v n m -> QDiagram b v n m #

Attach an atomic name to a certain subdiagram, computed from the given diagram /with the mapping from name to subdiagram included/. The upshot of this knot-tying is that if d' = d # named x, then lookupName x d' == Just d' (instead of Just d).

withName :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> (Subdiagram b v n m -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m #

Given a name and a diagram transformation indexed by a subdiagram, perform the transformation using the most recent subdiagram associated with (some qualification of) the name, or perform the identity transformation if the name does not exist.

withNameAll :: (IsName nm, Metric v, Semigroup m, OrderedField n) => nm -> ([Subdiagram b v n m] -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m #

Given a name and a diagram transformation indexed by a list of subdiagrams, perform the transformation using the collection of all such subdiagrams associated with (some qualification of) the given name.

withNames :: (IsName nm, Metric v, Semigroup m, OrderedField n) => [nm] -> ([Subdiagram b v n m] -> QDiagram b v n m -> QDiagram b v n m) -> QDiagram b v n m -> QDiagram b v n m #

Given a list of names and a diagram transformation indexed by a list of subdiagrams, perform the transformation using the list of most recent subdiagrams associated with (some qualification of) each name. Do nothing (the identity transformation) if any of the names do not exist.

localize :: forall b v n m. (Metric v, OrderedField n, Semigroup m) => QDiagram b v n m -> QDiagram b v n m #

"Localize" a diagram by hiding all the names, so they are no longer visible to the outside.

href :: (Metric v, OrderedField n, Semigroup m) => String -> QDiagram b v n m -> QDiagram b v n m #

Make a diagram into a hyperlink. Note that only some backends will honor hyperlink annotations.

opacityGroup :: (Metric v, OrderedField n, Semigroup m) => Double -> QDiagram b v n m -> QDiagram b v n m #

Change the transparency of a Diagram as a group.

groupOpacity :: (Metric v, OrderedField n, Semigroup m) => Double -> QDiagram b v n m -> QDiagram b v n m #

Change the transparency of a Diagram as a group.

setEnvelope :: forall b v n m. (OrderedField n, Metric v, Monoid' m) => Envelope v n -> QDiagram b v n m -> QDiagram b v n m #

Replace the envelope of a diagram.

setTrace :: forall b v n m. (OrderedField n, Metric v, Semigroup m) => Trace v n -> QDiagram b v n m -> QDiagram b v n m #

Replace the trace of a diagram.

atop :: (OrderedField n, Metric v, Semigroup m) => QDiagram b v n m -> QDiagram b v n m -> QDiagram b v n m infixl 6 #

A convenient synonym for mappend on diagrams, designed to be used infix (to help remember which diagram goes on top of which when combining them, namely, the first on top of the second).

Subdiagrams

data Subdiagram b v n m #

A Subdiagram represents a diagram embedded within the context of a larger diagram. Essentially, it consists of a diagram paired with any accumulated information from the larger context (transformations, attributes, etc.).

Constructors

Subdiagram (QDiagram b v n m) (DownAnnots v n) 
Instances
Functor (Subdiagram b v n) # 
Instance details

Defined in Diagrams.Core.Types

Methods

fmap :: (a -> b0) -> Subdiagram b v n a -> Subdiagram b v n b0 #

(<$) :: a -> Subdiagram b v n b0 -> Subdiagram b v n a #

(Metric v, OrderedField n) => HasOrigin (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

moveOriginTo :: Point (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) -> Subdiagram b v n m -> Subdiagram b v n m #

Transformable (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

transform :: Transformation (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) -> Subdiagram b v n m -> Subdiagram b v n m #

(OrderedField n, Metric v, Semigroup m) => Traced (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getTrace :: Subdiagram b v n m -> Trace (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) #

(OrderedField n, Metric v, Monoid' m) => Enveloped (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

Methods

getEnvelope :: Subdiagram b v n m -> Envelope (V (Subdiagram b v n m)) (N (Subdiagram b v n m)) #

type N (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type N (Subdiagram b v n m) = n
type V (Subdiagram b v n m) # 
Instance details

Defined in Diagrams.Core.Types

type V (Subdiagram b v n m) = v

mkSubdiagram :: QDiagram b v n m -> Subdiagram b v n m #

Turn a diagram into a subdiagram with no accumulated context.

getSub :: (Metric v, OrderedField n, Semigroup m) => Subdiagram b v n m -> QDiagram b v n m #

Turn a subdiagram into a normal diagram, including the enclosing context. Concretely, a subdiagram is a pair of (1) a diagram and (2) a "context" consisting of an extra transformation and attributes. getSub simply applies the transformation and attributes to the diagram to get the corresponding "top-level" diagram.

rawSub :: Subdiagram b v n m -> QDiagram b v n m #

Extract the "raw" content of a subdiagram, by throwing away the context.

location :: (Additive v, Num n) => Subdiagram b v n m -> Point v n #

Get the location of a subdiagram; that is, the location of its local origin with respect to the vector space of its parent diagram. In other words, the point where its local origin "ended up".

subPoint :: (Metric v, OrderedField n) => Point v n -> Subdiagram b v n m #

Create a "point subdiagram", that is, a pointDiagram (with no content and a point envelope) treated as a subdiagram with local origin at the given point. Note this is not the same as mkSubdiagram . pointDiagram, which would result in a subdiagram with local origin at the parent origin, rather than at the given point.

Measurements

data Measured n a #

'Measured n a' is an object that depends on local, normalized and global scales. The normalized and global scales are calculated when rendering a diagram.

For attributes, the local scale gets multiplied by the average scale of the transform.

Instances
Profunctor Measured # 
Instance details

Defined in Diagrams.Core.Measure

Methods

dimap :: (a -> b) -> (c -> d) -> Measured b c -> Measured a d #

lmap :: (a -> b) -> Measured b c -> Measured a c #

rmap :: (b -> c) -> Measured a b -> Measured a c #

(#.) :: Coercible c b => q b c -> Measured a b -> Measured a c #

(.#) :: Coercible b a => Measured b c -> q a b -> Measured a c #

Monad (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

(>>=) :: Measured n a -> (a -> Measured n b) -> Measured n b #

(>>) :: Measured n a -> Measured n b -> Measured n b #

return :: a -> Measured n a #

fail :: String -> Measured n a #

Functor (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

fmap :: (a -> b) -> Measured n a -> Measured n b #

(<$) :: a -> Measured n b -> Measured n a #

Applicative (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

pure :: a -> Measured n a #

(<*>) :: Measured n (a -> b) -> Measured n a -> Measured n b #

liftA2 :: (a -> b -> c) -> Measured n a -> Measured n b -> Measured n c #

(*>) :: Measured n a -> Measured n b -> Measured n b #

(<*) :: Measured n a -> Measured n b -> Measured n a #

Distributive (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

distribute :: Functor f => f (Measured n a) -> Measured n (f a) #

collect :: Functor f => (a -> Measured n b) -> f a -> Measured n (f b) #

distributeM :: Monad m => m (Measured n a) -> Measured n (m a) #

collectM :: Monad m => (a -> Measured n b) -> m a -> Measured n (m b) #

Representable (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Associated Types

type Rep (Measured n) :: Type #

Methods

tabulate :: (Rep (Measured n) -> a) -> Measured n a #

index :: Measured n a -> Rep (Measured n) -> a #

Additive (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

zero :: Num a => Measured n a #

(^+^) :: Num a => Measured n a -> Measured n a -> Measured n a #

(^-^) :: Num a => Measured n a -> Measured n a -> Measured n a #

lerp :: Num a => a -> Measured n a -> Measured n a -> Measured n a #

liftU2 :: (a -> a -> a) -> Measured n a -> Measured n a -> Measured n a #

liftI2 :: (a -> b -> c) -> Measured n a -> Measured n b -> Measured n c #

Floating a => Floating (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

pi :: Measured n a #

exp :: Measured n a -> Measured n a #

log :: Measured n a -> Measured n a #

sqrt :: Measured n a -> Measured n a #

(**) :: Measured n a -> Measured n a -> Measured n a #

logBase :: Measured n a -> Measured n a -> Measured n a #

sin :: Measured n a -> Measured n a #

cos :: Measured n a -> Measured n a #

tan :: Measured n a -> Measured n a #

asin :: Measured n a -> Measured n a #

acos :: Measured n a -> Measured n a #

atan :: Measured n a -> Measured n a #

sinh :: Measured n a -> Measured n a #

cosh :: Measured n a -> Measured n a #

tanh :: Measured n a -> Measured n a #

asinh :: Measured n a -> Measured n a #

acosh :: Measured n a -> Measured n a #

atanh :: Measured n a -> Measured n a #

log1p :: Measured n a -> Measured n a #

expm1 :: Measured n a -> Measured n a #

log1pexp :: Measured n a -> Measured n a #

log1mexp :: Measured n a -> Measured n a #

Fractional a => Fractional (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

(/) :: Measured n a -> Measured n a -> Measured n a #

recip :: Measured n a -> Measured n a #

fromRational :: Rational -> Measured n a #

Num a => Num (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

(+) :: Measured n a -> Measured n a -> Measured n a #

(-) :: Measured n a -> Measured n a -> Measured n a #

(*) :: Measured n a -> Measured n a -> Measured n a #

negate :: Measured n a -> Measured n a #

abs :: Measured n a -> Measured n a #

signum :: Measured n a -> Measured n a #

fromInteger :: Integer -> Measured n a #

Semigroup a => Semigroup (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

(<>) :: Measured n a -> Measured n a -> Measured n a #

sconcat :: NonEmpty (Measured n a) -> Measured n a #

stimes :: Integral b => b -> Measured n a -> Measured n a #

Monoid a => Monoid (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

mempty :: Measured n a #

mappend :: Measured n a -> Measured n a -> Measured n a #

mconcat :: [Measured n a] -> Measured n a #

HasOrigin t => HasOrigin (Measured n t) # 
Instance details

Defined in Diagrams.Core.HasOrigin

Methods

moveOriginTo :: Point (V (Measured n t)) (N (Measured n t)) -> Measured n t -> Measured n t #

(InSpace v n t, Transformable t, HasLinearMap v, Floating n) => Transformable (Measured n t) # 
Instance details

Defined in Diagrams.Core.Transform

Methods

transform :: Transformation (V (Measured n t)) (N (Measured n t)) -> Measured n t -> Measured n t #

HasStyle b => HasStyle (Measured n b) # 
Instance details

Defined in Diagrams.Core.Style

Methods

applyStyle :: Style (V (Measured n b)) (N (Measured n b)) -> Measured n b -> Measured n b #

Qualifiable a => Qualifiable (Measured n a) # 
Instance details

Defined in Diagrams.Core.Names

Methods

(.>>) :: IsName a0 => a0 -> Measured n a -> Measured n a #

Juxtaposable a => Juxtaposable (Measured n a) # 
Instance details

Defined in Diagrams.Core.Juxtapose

Methods

juxtapose :: Vn (Measured n a) -> Measured n a -> Measured n a -> Measured n a #

MonadReader (n, n, n) (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

Methods

ask :: Measured n (n, n, n) #

local :: ((n, n, n) -> (n, n, n)) -> Measured n a -> Measured n a #

reader :: ((n, n, n) -> a) -> Measured n a #

type Rep (Measured n) # 
Instance details

Defined in Diagrams.Core.Measure

type Rep (Measured n) = (n, n, n)
type N (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

type N (Measured n a) = N a
type V (Measured n a) # 
Instance details

Defined in Diagrams.Core.Measure

type V (Measured n a) = V a

type Measure n = Measured n n #

A measure is a Measured number.

fromMeasured :: Num n => n -> n -> Measured n a -> a #

fromMeasured globalScale normalizedScale measure -> a

output :: n -> Measure n #

Output units don't change.

local :: Num n => n -> Measure n #

Local units are scaled by the average scale of a transform.

global :: Num n => n -> Measure n #

Global units are scaled so that they are interpreted relative to the size of the final rendered diagram.

normalized :: Num n => n -> Measure n #

Normalized units get scaled so that one normalized unit is the size of the final diagram.

scaleLocal :: Num n => n -> Measured n a -> Measured n a #

Scale the local units of a Measured thing.

atLeast :: Ord n => Measure n -> Measure n -> Measure n #

Calculate the smaller of two measures.

atMost :: Ord n => Measure n -> Measure n -> Measure n #

Calculate the larger of two measures.

Backends

class Backend b v n where #

Abstract diagrams are rendered to particular formats by backends. Each backend/vector space combination must be an instance of the Backend class.

A minimal complete definition consists of Render, Result, Options, and renderRTree. However, most backends will want to implement adjustDia as well; the default definition does nothing. Some useful standard definitions are provided in the Diagrams.TwoD.Adjust module from the diagrams-lib package.

Minimal complete definition

renderRTree

Associated Types

data Render b v n :: * #

An intermediate representation used for rendering primitives. (Typically, this will be some sort of monad, but it need not be.) The Renderable class guarantees that a backend will be able to convert primitives into this type; how these rendered primitives are combined into an ultimate Result is completely up to the backend.

type Result b v n :: * #

The result of running/interpreting a rendering operation.

data Options b v n :: * #

Backend-specific rendering options.

Methods

adjustDia :: (Additive v, Monoid' m, Num n) => b -> Options b v n -> QDiagram b v n m -> (Options b v n, Transformation v n, QDiagram b v n m) #

adjustDia allows the backend to make adjustments to the final diagram (e.g. to adjust the size based on the options) before rendering it. It returns a modified options record, the transformation applied to the diagram (which can be used to convert attributes whose value is Measure, or transform e.g. screen coordinates back into local diagram coordinates), and the adjusted diagram itself.

See the diagrams-lib package (particularly the Diagrams.TwoD.Adjust module) for some useful implementations.

renderRTree :: b -> Options b v n -> RTree b v n Annotation -> Result b v n #

Given some options, take a representation of a diagram as a tree and render it. The RTree has already been simplified and has all measurements converted to Output units.

Instances
Backend NullBackend v n # 
Instance details

Defined in Diagrams.Core.Types

Associated Types

data Render NullBackend v n :: Type #

type Result NullBackend v n :: Type #

data Options NullBackend v n :: Type #

class Transformable t => Renderable t b where #

The Renderable type class connects backends to primitives which they know how to render.

Methods

render :: b -> t -> Render b (V t) (N t) #

Given a token representing the backend and a transformable object, render it in the appropriate rendering context.

Instances
Renderable (Prim b v n) b #

The Renderable instance for Prim just pushes calls to render down through the Prim constructor.

Instance details

Defined in Diagrams.Core.Types

Methods

render :: b -> Prim b v n -> Render b (V (Prim b v n)) (N (Prim b v n)) #

renderDia :: (Backend b v n, HasLinearMap v, Metric v, Typeable n, OrderedField n, Monoid' m) => b -> Options b v n -> QDiagram b v n m -> Result b v n #

Render a diagram.

renderDiaT :: (Backend b v n, HasLinearMap v, Metric v, Typeable n, OrderedField n, Monoid' m) => b -> Options b v n -> QDiagram b v n m -> (Transformation v n, Result b v n) #

Render a diagram, returning also the transformation which was used to convert the diagram from its ("global") coordinate system into the output coordinate system. The inverse of this transformation can be used, for example, to convert output/screen coordinates back into diagram coordinates. See also adjustDia.

The null backend

data NullBackend #

A null backend which does no actual rendering. It is provided mainly for convenience in situations where you must give a diagram a concrete, monomorphic type, but don't actually care which one. See D for more explanation and examples.

It is courteous, when defining a new primitive P, to make an instance

instance Renderable P NullBackend where
  render _ _ = mempty

This ensures that the trick with D annotations can be used for diagrams containing your primitive.

Instances
Backend NullBackend v n # 
Instance details

Defined in Diagrams.Core.Types

Associated Types

data Render NullBackend v n :: Type #

type Result NullBackend v n :: Type #

data Options NullBackend v n :: Type #

Semigroup (Render NullBackend v n) # 
Instance details

Defined in Diagrams.Core.Types

Monoid (Render NullBackend v n) # 
Instance details

Defined in Diagrams.Core.Types

data Render NullBackend v n # 
Instance details

Defined in Diagrams.Core.Types

data Options NullBackend v n # 
Instance details

Defined in Diagrams.Core.Types

type Result NullBackend v n # 
Instance details

Defined in Diagrams.Core.Types

type Result NullBackend v n = ()

type D v n = QDiagram NullBackend v n Any #

The D type is provided for convenience in situations where you must give a diagram a concrete, monomorphic type, but don't care which one. Such situations arise when you pass a diagram to a function which is polymorphic in its input but monomorphic in its output, such as width, height, phantom, or names. Such functions compute some property of the diagram, or use it to accomplish some other purpose, but do not result in the diagram being rendered. If the diagram does not have a monomorphic type, GHC complains that it cannot determine the diagram's type.

For example, here is the error we get if we try to compute the width of an image (this example requires diagrams-lib):

  ghci> width (image (uncheckedImageRef "foo.png" 200 200))
  <interactive>:11:8:
      No instance for (Renderable (DImage n0 External) b0)
        arising from a use of image
      The type variables n0, b0 are ambiguous
      Possible fix: add a type signature that fixes these type variable(s)
      Note: there is a potential instance available:
        instance Fractional n => Renderable (DImage n a) NullBackend
          -- Defined in Image
      Possible fix:
        add an instance declaration for
        (Renderable (DImage n0 External) b0)
      In the first argument of width, namely
        `(image (uncheckedImageRef "foo.png" 200 200))'
      In the expression:
        width (image (uncheckedImageRef "foo.png" 200 200))
      In an equation for it:
          it = width (image (uncheckedImageRef "foo.png" 200 200))
  

GHC complains that there is no instance for Renderable (DImage n0 External) b0; what is really going on is that it does not have enough information to decide what backend to use (hence the uninstantiated n0 and b0). This is annoying because we know that the choice of backend cannot possibly affect the width of the image (it's 200! it's right there in the code!); but there is no way for GHC to know that.

The solution is to annotate the call to image with the type D V2 Double, like so:

  ghci> width (image (uncheckedImageRef "foo.png" 200 200) :: D V2 Double)
  200.00000000000006
  

(It turns out the width wasn't 200 after all...)

As another example, here is the error we get if we try to compute the width of a radius-1 circle:

  ghci> width (circle 1)
  <interactive>:12:1:
      Couldn't match expected type V2 with actual type `V a0'
      The type variable a0 is ambiguous
      Possible fix: add a type signature that fixes these type variable(s)
      In the expression: width (circle 1)
      In an equation for it: it = width (circle 1)
  

There's even more ambiguity here. Whereas image always returns a Diagram, the circle function can produce any TrailLike type, and the width function can consume any Enveloped type, so GHC has no idea what type to pick to go in the middle. However, the solution is the same:

  ghci> width (circle 1 :: D V2 Double)
  1.9999999999999998
  

Convenience classes

type HasLinearMap v = (HasBasis v, Traversable v) #

HasLinearMap is a constraint synonym, just to help shorten some of the ridiculously long constraint sets.

type HasBasis v = (Additive v, Representable v, Rep v ~ E v) #

An Additive vector space whose representation is made up of basis elements.

type OrderedField s = (Floating s, Ord s) #

When dealing with envelopes we often want scalars to be an ordered field (i.e. support all four arithmetic operations and be totally ordered) so we introduce this constraint as a convenient shorthand.

type TypeableFloat n = (Typeable n, RealFloat n) #

Constraint for numeric types that are RealFloat and Typeable, which often occur together. This is used to shorten shorten type constraint contexts.

type Monoid' = Monoid #

For base < 4.11, the Monoid' constraint is a synonym for things which are instances of both Semigroup and Monoid. For base version 4.11 and onwards, Monoid has Semigroup as a superclass already, so for backwards compatibility Monoid' is provided as a synonym for Monoid.