diagrams-lib-1.4.5.3: Embedded domain-specific language for declarative graphics
Copyright(c) 2011-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

Diagrams.TwoD

Description

This module defines the two-dimensional vector space R^2, two-dimensional transformations, and various predefined two-dimensional shapes. This module re-exports useful functionality from a group of more specific modules:

Synopsis

R^2

data V2 a #

A 2-dimensional vector

>>> pure 1 :: V2 Int
V2 1 1
>>> V2 1 2 + V2 3 4
V2 4 6
>>> V2 1 2 * V2 3 4
V2 3 8
>>> sum (V2 1 2)
3

Constructors

V2 !a !a 

Instances

Instances details
Representable V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep V2 #

Methods

tabulate :: (Rep V2 -> a) -> V2 a #

index :: V2 a -> Rep V2 -> a #

MonadFix V2 
Instance details

Defined in Linear.V2

Methods

mfix :: (a -> V2 a) -> V2 a #

MonadZip V2 
Instance details

Defined in Linear.V2

Methods

mzip :: V2 a -> V2 b -> V2 (a, b) #

mzipWith :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

munzip :: V2 (a, b) -> (V2 a, V2 b) #

Foldable V2 
Instance details

Defined in Linear.V2

Methods

fold :: Monoid m => V2 m -> m #

foldMap :: Monoid m => (a -> m) -> V2 a -> m #

foldMap' :: Monoid m => (a -> m) -> V2 a -> m #

foldr :: (a -> b -> b) -> b -> V2 a -> b #

foldr' :: (a -> b -> b) -> b -> V2 a -> b #

foldl :: (b -> a -> b) -> b -> V2 a -> b #

foldl' :: (b -> a -> b) -> b -> V2 a -> b #

foldr1 :: (a -> a -> a) -> V2 a -> a #

foldl1 :: (a -> a -> a) -> V2 a -> a #

toList :: V2 a -> [a] #

null :: V2 a -> Bool #

length :: V2 a -> Int #

elem :: Eq a => a -> V2 a -> Bool #

maximum :: Ord a => V2 a -> a #

minimum :: Ord a => V2 a -> a #

sum :: Num a => V2 a -> a #

product :: Num a => V2 a -> a #

Eq1 V2 
Instance details

Defined in Linear.V2

Methods

liftEq :: (a -> b -> Bool) -> V2 a -> V2 b -> Bool #

Ord1 V2 
Instance details

Defined in Linear.V2

Methods

liftCompare :: (a -> b -> Ordering) -> V2 a -> V2 b -> Ordering #

Read1 V2 
Instance details

Defined in Linear.V2

Methods

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

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

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (V2 a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [V2 a] #

Show1 V2 
Instance details

Defined in Linear.V2

Methods

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

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

Traversable V2 
Instance details

Defined in Linear.V2

Methods

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

sequenceA :: Applicative f => V2 (f a) -> f (V2 a) #

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

sequence :: Monad m => V2 (m a) -> m (V2 a) #

Applicative V2 
Instance details

Defined in Linear.V2

Methods

pure :: a -> V2 a #

(<*>) :: V2 (a -> b) -> V2 a -> V2 b #

liftA2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

(*>) :: V2 a -> V2 b -> V2 b #

(<*) :: V2 a -> V2 b -> V2 a #

Functor V2 
Instance details

Defined in Linear.V2

Methods

fmap :: (a -> b) -> V2 a -> V2 b #

(<$) :: a -> V2 b -> V2 a #

Monad V2 
Instance details

Defined in Linear.V2

Methods

(>>=) :: V2 a -> (a -> V2 b) -> V2 b #

(>>) :: V2 a -> V2 b -> V2 b #

return :: a -> V2 a #

Serial1 V2 
Instance details

Defined in Linear.V2

Methods

serializeWith :: MonadPut m => (a -> m ()) -> V2 a -> m () #

deserializeWith :: MonadGet m => m a -> m (V2 a) #

HasTheta V2 Source # 
Instance details

Defined in Diagrams.TwoD.Types

Methods

_theta :: RealFloat n => Lens' (V2 n) (Angle n) Source #

HasR V2 Source # 
Instance details

Defined in Diagrams.TwoD.Types

Methods

_r :: RealFloat n => Lens' (V2 n) n Source #

Distributive V2 
Instance details

Defined in Linear.V2

Methods

distribute :: Functor f => f (V2 a) -> V2 (f a) #

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

distributeM :: Monad m => m (V2 a) -> V2 (m a) #

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

Hashable1 V2 
Instance details

Defined in Linear.V2

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> V2 a -> Int #

Affine V2 
Instance details

Defined in Linear.Affine

Associated Types

type Diff V2 :: Type -> Type #

Methods

(.-.) :: Num a => V2 a -> V2 a -> Diff V2 a #

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

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

Metric V2 
Instance details

Defined in Linear.V2

Methods

dot :: Num a => V2 a -> V2 a -> a #

quadrance :: Num a => V2 a -> a #

qd :: Num a => V2 a -> V2 a -> a #

distance :: Floating a => V2 a -> V2 a -> a #

norm :: Floating a => V2 a -> a #

signorm :: Floating a => V2 a -> V2 a #

Trace V2 
Instance details

Defined in Linear.Trace

Methods

trace :: Num a => V2 (V2 a) -> a #

diagonal :: V2 (V2 a) -> V2 a #

Finite V2 
Instance details

Defined in Linear.V2

Associated Types

type Size V2 :: Nat #

Methods

toV :: V2 a -> V (Size V2) a #

fromV :: V (Size V2) a -> V2 a #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a #

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

Additive V2 
Instance details

Defined in Linear.V2

Methods

zero :: Num a => V2 a #

(^+^) :: Num a => V2 a -> V2 a -> V2 a #

(^-^) :: Num a => V2 a -> V2 a -> V2 a #

lerp :: Num a => a -> V2 a -> V2 a -> V2 a #

liftU2 :: (a -> a -> a) -> V2 a -> V2 a -> V2 a #

liftI2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Apply V2 
Instance details

Defined in Linear.V2

Methods

(<.>) :: V2 (a -> b) -> V2 a -> V2 b #

(.>) :: V2 a -> V2 b -> V2 b #

(<.) :: V2 a -> V2 b -> V2 a #

liftF2 :: (a -> b -> c) -> V2 a -> V2 b -> V2 c #

Bind V2 
Instance details

Defined in Linear.V2

Methods

(>>-) :: V2 a -> (a -> V2 b) -> V2 b #

join :: V2 (V2 a) -> V2 a #

Foldable1 V2 
Instance details

Defined in Linear.V2

Methods

fold1 :: Semigroup m => V2 m -> m #

foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m #

toNonEmpty :: V2 a -> NonEmpty a #

Traversable1 V2 
Instance details

Defined in Linear.V2

Methods

traverse1 :: Apply f => (a -> f b) -> V2 a -> f (V2 b) #

sequence1 :: Apply f => V2 (f b) -> f (V2 b) #

Generic1 V2 
Instance details

Defined in Linear.V2

Associated Types

type Rep1 V2 :: k -> Type #

Methods

from1 :: forall (a :: k). V2 a -> Rep1 V2 a #

to1 :: forall (a :: k). Rep1 V2 a -> V2 a #

Num r => Coalgebra r (E V2) 
Instance details

Defined in Linear.Algebra

Methods

comult :: (E V2 -> r) -> E V2 -> E V2 -> r #

counital :: (E V2 -> r) -> r #

Unbox a => Vector Vector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) #

basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) #

basicLength :: Vector (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) #

basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) #

basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () #

elemseq :: Vector (V2 a) -> V2 a -> b -> b #

Unbox a => MVector MVector (V2 a) 
Instance details

Defined in Linear.V2

Methods

basicLength :: MVector s (V2 a) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) #

basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool #

basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) #

basicInitialize :: MVector s (V2 a) -> ST s () #

basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) #

basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) #

basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () #

basicClear :: MVector s (V2 a) -> ST s () #

basicSet :: MVector s (V2 a) -> V2 a -> ST s () #

basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () #

basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () #

basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) #

Data a => Data (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

toConstr :: V2 a -> Constr #

dataTypeOf :: V2 a -> DataType #

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

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

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

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

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

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

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

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

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

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

Storable a => Storable (V2 a) 
Instance details

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int #

alignment :: V2 a -> Int #

peekElemOff :: Ptr (V2 a) -> Int -> IO (V2 a) #

pokeElemOff :: Ptr (V2 a) -> Int -> V2 a -> IO () #

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

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

peek :: Ptr (V2 a) -> IO (V2 a) #

poke :: Ptr (V2 a) -> V2 a -> IO () #

Monoid a => Monoid (V2 a) 
Instance details

Defined in Linear.V2

Methods

mempty :: V2 a #

mappend :: V2 a -> V2 a -> V2 a #

mconcat :: [V2 a] -> V2 a #

Semigroup a => Semigroup (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

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

stimes :: Integral b => b -> V2 a -> V2 a #

Bounded a => Bounded (V2 a) 
Instance details

Defined in Linear.V2

Methods

minBound :: V2 a #

maxBound :: V2 a #

Floating a => Floating (V2 a) 
Instance details

Defined in Linear.V2

Methods

pi :: V2 a #

exp :: V2 a -> V2 a #

log :: V2 a -> V2 a #

sqrt :: V2 a -> V2 a #

(**) :: V2 a -> V2 a -> V2 a #

logBase :: V2 a -> V2 a -> V2 a #

sin :: V2 a -> V2 a #

cos :: V2 a -> V2 a #

tan :: V2 a -> V2 a #

asin :: V2 a -> V2 a #

acos :: V2 a -> V2 a #

atan :: V2 a -> V2 a #

sinh :: V2 a -> V2 a #

cosh :: V2 a -> V2 a #

tanh :: V2 a -> V2 a #

asinh :: V2 a -> V2 a #

acosh :: V2 a -> V2 a #

atanh :: V2 a -> V2 a #

log1p :: V2 a -> V2 a #

expm1 :: V2 a -> V2 a #

log1pexp :: V2 a -> V2 a #

log1mexp :: V2 a -> V2 a #

Generic (V2 a) 
Instance details

Defined in Linear.V2

Associated Types

type Rep (V2 a) :: Type -> Type #

Methods

from :: V2 a -> Rep (V2 a) x #

to :: Rep (V2 a) x -> V2 a #

Ix a => Ix (V2 a) 
Instance details

Defined in Linear.V2

Methods

range :: (V2 a, V2 a) -> [V2 a] #

index :: (V2 a, V2 a) -> V2 a -> Int #

unsafeIndex :: (V2 a, V2 a) -> V2 a -> Int #

inRange :: (V2 a, V2 a) -> V2 a -> Bool #

rangeSize :: (V2 a, V2 a) -> Int #

unsafeRangeSize :: (V2 a, V2 a) -> Int #

Num a => Num (V2 a) 
Instance details

Defined in Linear.V2

Methods

(+) :: V2 a -> V2 a -> V2 a #

(-) :: V2 a -> V2 a -> V2 a #

(*) :: V2 a -> V2 a -> V2 a #

negate :: V2 a -> V2 a #

abs :: V2 a -> V2 a #

signum :: V2 a -> V2 a #

fromInteger :: Integer -> V2 a #

Read a => Read (V2 a) 
Instance details

Defined in Linear.V2

Fractional a => Fractional (V2 a) 
Instance details

Defined in Linear.V2

Methods

(/) :: V2 a -> V2 a -> V2 a #

recip :: V2 a -> V2 a #

fromRational :: Rational -> V2 a #

Show a => Show (V2 a) 
Instance details

Defined in Linear.V2

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Binary a => Binary (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: V2 a -> Put #

get :: Get (V2 a) #

putList :: [V2 a] -> Put #

Serial a => Serial (V2 a) 
Instance details

Defined in Linear.V2

Methods

serialize :: MonadPut m => V2 a -> m () #

deserialize :: MonadGet m => m (V2 a) #

Serialize a => Serialize (V2 a) 
Instance details

Defined in Linear.V2

Methods

put :: Putter (V2 a) #

get :: Get (V2 a) #

NFData a => NFData (V2 a) 
Instance details

Defined in Linear.V2

Methods

rnf :: V2 a -> () #

Transformable (V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Types

Methods

transform :: Transformation (V (V2 n)) (N (V2 n)) -> V2 n -> V2 n #

Coordinates (V2 n) Source # 
Instance details

Defined in Diagrams.Coordinates

Associated Types

type FinalCoord (V2 n) Source #

type PrevDim (V2 n) Source #

type Decomposition (V2 n) Source #

Methods

(^&) :: PrevDim (V2 n) -> FinalCoord (V2 n) -> V2 n Source #

pr :: PrevDim (V2 n) -> FinalCoord (V2 n) -> V2 n Source #

coords :: V2 n -> Decomposition (V2 n) Source #

Eq a => Eq (V2 a) 
Instance details

Defined in Linear.V2

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Ord a => Ord (V2 a) 
Instance details

Defined in Linear.V2

Methods

compare :: V2 a -> V2 a -> Ordering #

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

(<=) :: V2 a -> V2 a -> Bool #

(>) :: V2 a -> V2 a -> Bool #

(>=) :: V2 a -> V2 a -> Bool #

max :: V2 a -> V2 a -> V2 a #

min :: V2 a -> V2 a -> V2 a #

Hashable a => Hashable (V2 a) 
Instance details

Defined in Linear.V2

Methods

hashWithSalt :: Int -> V2 a -> Int #

hash :: V2 a -> Int #

Ixed (V2 a) 
Instance details

Defined in Linear.V2

Methods

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

Epsilon a => Epsilon (V2 a) 
Instance details

Defined in Linear.V2

Methods

nearZero :: V2 a -> Bool #

Random a => Random (V2 a) 
Instance details

Defined in Linear.V2

Methods

randomR :: RandomGen g => (V2 a, V2 a) -> g -> (V2 a, g) #

random :: RandomGen g => g -> (V2 a, g) #

randomRs :: RandomGen g => (V2 a, V2 a) -> g -> [V2 a] #

randoms :: RandomGen g => g -> [V2 a] #

Unbox a => Unbox (V2 a) 
Instance details

Defined in Linear.V2

RealFloat n => HasQuery (Located (Trail V2 n)) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

RealFloat n => HasQuery (Located (Trail' l V2 n)) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getQuery :: Located (Trail' l V2 n) -> Query (V (Located (Trail' l V2 n))) (N (Located (Trail' l V2 n))) Crossings Source #

FoldableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m #

ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

ifoldr' :: (E V2 -> a -> b -> b) -> b -> V2 a -> b #

ifoldl' :: (E V2 -> b -> a -> b) -> b -> V2 a -> b #

FunctorWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

imap :: (E V2 -> a -> b) -> V2 a -> V2 b #

TraversableWithIndex (E V2) V2 
Instance details

Defined in Linear.V2

Methods

itraverse :: Applicative f => (E V2 -> a -> f b) -> V2 a -> f (V2 b) #

Lift a => Lift (V2 a :: Type) 
Instance details

Defined in Linear.V2

Methods

lift :: Quote m => V2 a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => V2 a -> Code m (V2 a) #

Each (V2 a) (V2 b) a b 
Instance details

Defined in Linear.V2

Methods

each :: Traversal (V2 a) (V2 b) a b #

Field1 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_1 :: Lens (V2 a) (V2 a) a a #

Field2 (V2 a) (V2 a) a a 
Instance details

Defined in Linear.V2

Methods

_2 :: Lens (V2 a) (V2 a) a a #

RealFloat n => Traced (BoundingBox V2 n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

getTrace :: BoundingBox V2 n -> Trace (V (BoundingBox V2 n)) (N (BoundingBox V2 n)) #

RealFloat n => Traced (Path V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getTrace :: Path V2 n -> Trace (V (Path V2 n)) (N (Path V2 n)) #

OrderedField n => Traced (FixedSegment V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Segment

RealFloat n => Traced (Trail V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getTrace :: Trail V2 n -> Trace (V (Trail V2 n)) (N (Trail V2 n)) #

RealFloat n => HasQuery (Path V2 n) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getQuery :: Path V2 n -> Query (V (Path V2 n)) (N (Path V2 n)) Crossings Source #

OrderedField n => Traced (Segment Closed V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Segment

(TypeableFloat n, Renderable (Path V2 n) b) => TrailLike (QDiagram b V2 n Any) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

trailLike :: Located (Trail (V (QDiagram b V2 n Any)) (N (QDiagram b V2 n Any))) -> QDiagram b V2 n Any Source #

type Rep V2 
Instance details

Defined in Linear.V2

type Rep V2 = E V2
type Diff V2 
Instance details

Defined in Linear.Affine

type Diff V2 = V2
type Size V2 
Instance details

Defined in Linear.V2

type Size V2 = 2
type Rep1 V2 
Instance details

Defined in Linear.V2

type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.21.10-GEBpjm9an2TLgCMSuXYUVR" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
data MVector s (V2 a) 
Instance details

Defined in Linear.V2

data MVector s (V2 a) = MV_V2 !Int !(MVector s a)
type Rep (V2 a) 
Instance details

Defined in Linear.V2

type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.21.10-GEBpjm9an2TLgCMSuXYUVR" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))
type N (V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Types

type N (V2 n) = n
type V (V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Types

type V (V2 n) = V2
type Decomposition (V2 n) Source # 
Instance details

Defined in Diagrams.Coordinates

type Decomposition (V2 n) = n :& n
type FinalCoord (V2 n) Source # 
Instance details

Defined in Diagrams.Coordinates

type FinalCoord (V2 n) = n
type PrevDim (V2 n) Source # 
Instance details

Defined in Diagrams.Coordinates

type PrevDim (V2 n) = n
type Index (V2 a) 
Instance details

Defined in Linear.V2

type Index (V2 a) = E V2
type IxValue (V2 a) 
Instance details

Defined in Linear.V2

type IxValue (V2 a) = a
data Vector (V2 a) 
Instance details

Defined in Linear.V2

data Vector (V2 a) = V_V2 !Int !(Vector a)

class R1 (t :: Type -> Type) where #

A space that has at least 1 basis vector _x.

Methods

_x :: Lens' (t a) a #

>>> V1 2 ^._x
2
>>> V1 2 & _x .~ 3
V1 3

Instances

Instances details
R1 Identity 
Instance details

Defined in Linear.V1

Methods

_x :: Lens' (Identity a) a #

R1 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_x :: Lens' (Quaternion a) a #

R1 V1 
Instance details

Defined in Linear.V1

Methods

_x :: Lens' (V1 a) a #

R1 V2 
Instance details

Defined in Linear.V2

Methods

_x :: Lens' (V2 a) a #

R1 V3 
Instance details

Defined in Linear.V3

Methods

_x :: Lens' (V3 a) a #

R1 V4 
Instance details

Defined in Linear.V4

Methods

_x :: Lens' (V4 a) a #

R1 f => R1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

class R1 t => R2 (t :: Type -> Type) where #

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

_xy

Methods

_y :: Lens' (t a) a #

>>> V2 1 2 ^._y
2
>>> V2 1 2 & _y .~ 3
V2 1 3

_xy :: Lens' (t a) (V2 a) #

Instances

Instances details
R2 Quaternion 
Instance details

Defined in Linear.Quaternion

Methods

_y :: Lens' (Quaternion a) a #

_xy :: Lens' (Quaternion a) (V2 a) #

R2 V2 
Instance details

Defined in Linear.V2

Methods

_y :: Lens' (V2 a) a #

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

R2 V3 
Instance details

Defined in Linear.V3

Methods

_y :: Lens' (V3 a) a #

_xy :: Lens' (V3 a) (V2 a) #

R2 V4 
Instance details

Defined in Linear.V4

Methods

_y :: Lens' (V4 a) a #

_xy :: Lens' (V4 a) (V2 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) #

type P2 = Point V2 Source #

r2 :: (n, n) -> V2 n Source #

Construct a 2D vector from a pair of components. See also &.

unr2 :: V2 n -> (n, n) Source #

Convert a 2D vector back into a pair of components. See also coords.

mkR2 :: n -> n -> V2 n Source #

Curried form of r2.

p2 :: (n, n) -> P2 n Source #

Construct a 2D point from a pair of coordinates. See also ^&.

unp2 :: P2 n -> (n, n) Source #

Convert a 2D point back into a pair of coordinates. See also coords.

mkP2 :: n -> n -> P2 n Source #

Curried form of p2.

unitX :: (R1 v, Additive v, Num n) => v n Source #

The unit vector in the positive X direction.

unitY :: (R2 v, Additive v, Num n) => v n Source #

The unit vector in the positive Y direction.

unit_X :: (R1 v, Additive v, Num n) => v n Source #

The unit vector in the negative X direction.

unit_Y :: (R2 v, Additive v, Num n) => v n Source #

The unit vector in the negative Y direction.

perp :: Num a => V2 a -> V2 a #

the counter-clockwise perpendicular vector

>>> perp $ V2 10 20
V2 (-20) 10

leftTurn :: (Num n, Ord n) => V2 n -> V2 n -> Bool Source #

leftTurn v1 v2 tests whether the direction of v2 is a left turn from v1 (that is, if the direction of v2 can be obtained from that of v1 by adding an angle 0 <= theta <= tau/2).

xDir :: (R1 v, Additive v, Num n) => Direction v n Source #

A Direction pointing in the X direction.

yDir :: (R2 v, Additive v, Num n) => Direction v n Source #

A Direction pointing in the Y direction.

Angles

tau :: Floating a => a Source #

The circle constant, the ratio of a circle's circumference to its radius. Note that pi = tau/2.

For more information and a well-reasoned argument why we should all be using tau instead of pi, see The Tau Manifesto, http://tauday.com/.

To hear what it sounds like (and to easily memorize the first 30 digits or so), try http://youtu.be/3174T-3-59Q.

angleV :: Floating n => Angle n -> V2 n Source #

A unit vector at a specified angle counter-clockwise from the positive x-axis

angleDir :: Floating n => Angle n -> Direction V2 n Source #

A direction at a specified angle counter-clockwise from the xDir.

signedAngleBetween :: RealFloat n => V2 n -> V2 n -> Angle n Source #

Signed angle between two vectors. Currently defined as

signedAngleBetween u v = (u ^. _theta) ^-^ (v ^. _theta)

signedAngleBetweenDirs :: RealFloat n => Direction V2 n -> Direction V2 n -> Angle n Source #

Same as signedAngleBetween but for Directionss.

Polar Coördinates

class HasR t where Source #

A space which has magnitude _r that can be calculated numerically.

Methods

_r :: RealFloat n => Lens' (t n) n Source #

Instances

Instances details
HasR V2 Source # 
Instance details

Defined in Diagrams.TwoD.Types

Methods

_r :: RealFloat n => Lens' (V2 n) n Source #

HasR V3 Source # 
Instance details

Defined in Diagrams.ThreeD.Types

Methods

_r :: RealFloat n => Lens' (V3 n) n Source #

HasR v => HasR (Point v) Source # 
Instance details

Defined in Diagrams.TwoD.Types

Methods

_r :: RealFloat n => Lens' (Point v n) n Source #

r2PolarIso :: RealFloat n => Iso' (V2 n) (n, Angle n) Source #

Paths

Stroking

stroke :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b) => t -> QDiagram b V2 n Any Source #

Convert a ToPath object into a diagram. The resulting diagram has the names 0, 1, ... assigned to each of the path's vertices.

See also stroke', which takes an extra options record allowing its behaviour to be customized.

stroke :: Path V2 Double                  -> Diagram b
stroke :: Located (Trail V2 Double)       -> Diagram b
stroke :: Located (Trail' Loop V2 Double) -> Diagram b
stroke :: Located (Trail' Line V2 Double) -> Diagram b

stroke' :: (InSpace V2 n t, ToPath t, TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> t -> QDiagram b V2 n Any Source #

A variant of stroke that takes an extra record of options to customize its behaviour. In particular:

  • Names can be assigned to the path's vertices

StrokeOpts is an instance of Default, so stroke' (with & ... ) syntax may be used.

strokePath :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any Source #

stroke specialised to Path.

strokeP :: (TypeableFloat n, Renderable (Path V2 n) b) => Path V2 n -> QDiagram b V2 n Any Source #

stroke specialised to Path.

strokePath' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any Source #

stroke' specialised to Path.

strokeP' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Path V2 n -> QDiagram b V2 n Any Source #

stroke' specialised to Path.

strokeTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any Source #

stroke specialised to Trail.

strokeT :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail V2 n -> QDiagram b V2 n Any Source #

stroke specialised to Trail.

strokeTrail' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any Source #

A composition of stroke' and pathFromTrail for conveniently converting a trail directly into a diagram.

strokeT' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName a) => StrokeOpts a -> Trail V2 n -> QDiagram b V2 n Any Source #

Deprecated synonym for strokeTrail'.

strokeLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Line V2 n -> QDiagram b V2 n Any Source #

A composition of strokeT and wrapLine for conveniently converting a line directly into a diagram.

strokeLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Trail' Loop V2 n -> QDiagram b V2 n Any Source #

A composition of strokeT and wrapLoop for conveniently converting a loop directly into a diagram.

strokeLocTrail :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any Source #

A convenience function for converting a Located Trail directly into a diagram; strokeLocTrail = stroke . trailLike.

strokeLocT :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail V2 n) -> QDiagram b V2 n Any Source #

Deprecated synonym for strokeLocTrail.

strokeLocLine :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Line V2 n) -> QDiagram b V2 n Any Source #

A convenience function for converting a Located line directly into a diagram; strokeLocLine = stroke . trailLike . mapLoc wrapLine.

strokeLocLoop :: (TypeableFloat n, Renderable (Path V2 n) b) => Located (Trail' Loop V2 n) -> QDiagram b V2 n Any Source #

A convenience function for converting a Located loop directly into a diagram; strokeLocLoop = stroke . trailLike . mapLoc wrapLoop.

data FillRule Source #

Enumeration of algorithms or "rules" for determining which points lie in the interior of a (possibly self-intersecting) path.

Constructors

Winding

Interior points are those with a nonzero winding number. See http://en.wikipedia.org/wiki/Nonzero-rule.

EvenOdd

Interior points are those where a ray extended infinitely in a particular direction crosses the path an odd number of times. See http://en.wikipedia.org/wiki/Even-odd_rule.

Instances

Instances details
Semigroup FillRule Source # 
Instance details

Defined in Diagrams.TwoD.Path

Show FillRule Source # 
Instance details

Defined in Diagrams.TwoD.Path

Default FillRule Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

def :: FillRule #

AttributeClass FillRule Source # 
Instance details

Defined in Diagrams.TwoD.Path

Eq FillRule Source # 
Instance details

Defined in Diagrams.TwoD.Path

Ord FillRule Source # 
Instance details

Defined in Diagrams.TwoD.Path

fillRule :: HasStyle a => FillRule -> a -> a Source #

Specify the fill rule that should be used for determining which points are inside a path.

_fillRule :: Lens' (Style V2 n) FillRule Source #

Lens onto the fill rule of a style.

data StrokeOpts a Source #

A record of options that control how a path is stroked. StrokeOpts is an instance of Default, so a StrokeOpts records can be created using with { ... } notation.

Constructors

StrokeOpts 

Fields

Instances

Instances details
Default (StrokeOpts a) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

def :: StrokeOpts a #

vertexNames :: Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']] Source #

Atomic names that should be assigned to the vertices of the path so that they can be referenced later. If there are not enough names, the extra vertices are not assigned names; if there are too many, the extra names are ignored. Note that this is a list of lists of names, since paths can consist of multiple trails. The first list of names are assigned to the vertices of the first trail, the second list to the second trail, and so on.

The default value is the empty list.

queryFillRule :: Lens' (StrokeOpts a) FillRule Source #

The fill rule used for determining which points are inside the path. The default is Winding. NOTE: for now, this only affects the resulting diagram's Query, not how it will be drawn! To set the fill rule determining how it is to be drawn, use the fillRule function.

intersectPoints :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => t -> s -> [P2 n] Source #

Find the intersect points of two objects that can be converted to a path.

intersectPoints' :: (InSpace V2 n t, SameSpace t s, ToPath t, ToPath s, OrderedField n) => n -> t -> s -> [P2 n] Source #

Find the intersect points of two objects that can be converted to a path within the given tolerance.

intersectPointsP :: OrderedField n => Path V2 n -> Path V2 n -> [P2 n] Source #

Compute the intersect points between two paths.

intersectPointsP' :: OrderedField n => n -> Path V2 n -> Path V2 n -> [P2 n] Source #

Compute the intersect points between two paths within given tolerance.

intersectPointsT :: OrderedField n => Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n] Source #

Compute the intersect points between two located trails.

intersectPointsT' :: OrderedField n => n -> Located (Trail V2 n) -> Located (Trail V2 n) -> [P2 n] Source #

Compute the intersect points between two located trails within the given tolerance.

Clipping

clipBy :: (HasStyle a, V a ~ V2, N a ~ n, TypeableFloat n) => Path V2 n -> a -> a Source #

Clip a diagram by the given path:

  • Only the parts of the diagram which lie in the interior of the path will be drawn.
  • The envelope of the diagram is unaffected.

clipTo :: TypeableFloat n => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Clip a diagram to the given path setting its envelope to the pointwise minimum of the envelopes of the diagram and path. The trace consists of those parts of the original diagram's trace which fall within the clipping path, or parts of the path's trace within the original diagram.

clipped :: TypeableFloat n => Path V2 n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Clip a diagram to the clip path taking the envelope and trace of the clip path.

_Clip :: Iso (Clip n) (Clip n') [Path V2 n] [Path V2 n'] Source #

_clip :: (Typeable n, OrderedField n) => Lens' (Style V2 n) [Path V2 n] Source #

Lens onto the Clip in a style. An empty list means no clipping.

Shapes

Rules

hrule :: (InSpace V2 n t, TrailLike t) => n -> t Source #

Create a centered horizontal (L-R) line of the given length.

hruleEx = vcat' (with & sep .~ 0.2) (map hrule [1..5])
        # centerXY # pad 1.1

vrule :: (InSpace V2 n t, TrailLike t) => n -> t Source #

Create a centered vertical (T-B) line of the given length.

vruleEx = hcat' (with & sep .~ 0.2) (map vrule [1, 1.2 .. 2])
        # centerXY # pad 1.1

Circle-ish things

unitCircle :: (TrailLike t, V t ~ V2, N t ~ n) => t Source #

A circle of radius 1, with center at the origin.

circle :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> t Source #

A circle of the given radius, centered at the origin. As a path, it begins at (r,0).

ellipse :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> t Source #

ellipse e constructs an ellipse with eccentricity e by scaling the unit circle in the X direction. The eccentricity must be within the interval [0,1).

ellipseXY :: (TrailLike t, V t ~ V2, N t ~ n, Transformable t) => n -> n -> t Source #

ellipseXY x y creates an axis-aligned ellipse, centered at the origin, with radius x along the x-axis and radius y along the y-axis.

arc :: (InSpace V2 n t, OrderedField n, TrailLike t) => Direction V2 n -> Angle n -> t Source #

Given a start direction d and a sweep angle s, arc d s is the path of a radius one arc starting at d and sweeping out the angle s counterclockwise (for positive s). The resulting Trail is allowed to wrap around and overlap itself.

arc' :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t Source #

Given a radus r, a start direction d and an angle s, arc' r d s is the path of a radius (abs r) arc starting at d and sweeping out the angle s counterclockwise (for positive s). The origin of the arc is its center.

arc'Ex = mconcat [ arc' r xDir (1/4 @@ turn) | r <- [0.5,-1,1.5] ]
       # centerXY # pad 1.1

arcCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t Source #

Like arcAngleCCW but clockwise.

arcCCW :: (InSpace V2 n t, RealFloat n, TrailLike t) => Direction V2 n -> Direction V2 n -> t Source #

Given a start direction s and end direction e, arcCCW s e is the path of a radius one arc counterclockwise between the two directions. The origin of the arc is its center.

wedge :: (InSpace V2 n t, OrderedField n, TrailLike t) => n -> Direction V2 n -> Angle n -> t Source #

Create a circular wedge of the given radius, beginning at the given direction and extending through the given angle.

wedgeEx = hcat' (with & sep .~ 0.5)
  [ wedge 1 xDir (1/4 @@ turn)
  , wedge 1 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn)
  , wedge 1 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn)
  ]
  # fc blue
  # centerXY # pad 1.1

arcBetween :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => Point V2 n -> Point V2 n -> n -> t Source #

arcBetween p q height creates an arc beginning at p and ending at q, with its midpoint at a distance of abs height away from the straight line from p to q. A positive value of height results in an arc to the left of the line from p to q; a negative value yields one to the right.

arcBetweenEx = mconcat
  [ arcBetween origin (p2 (2,1)) ht | ht <- [-0.2, -0.1 .. 0.2] ]
  # centerXY # pad 1.1

annularWedge :: (TrailLike t, V t ~ V2, N t ~ n, RealFloat n) => n -> n -> Direction V2 n -> Angle n -> t Source #

Create an annular wedge of the given radii, beginning at the first direction and extending through the given sweep angle. The radius of the outer circle is given first.

annularWedgeEx = hsep 0.50
  [ annularWedge 1 0.5 xDir (1/4 @@ turn)
  , annularWedge 1 0.3 (rotate (7/30 @@ turn) xDir) (4/30 @@ turn)
  , annularWedge 1 0.7 (rotate (1/8 @@ turn) xDir) (3/4 @@ turn)
  ]
  # fc blue
  # centerXY # pad 1.1

General polygons

polygon :: (InSpace V2 n t, TrailLike t) => PolygonOpts n -> t Source #

Generate the polygon described by the given options.

polyTrail :: OrderedField n => PolygonOpts n -> Located (Trail V2 n) Source #

Generate a polygon. See PolygonOpts for more information.

data PolygonOpts n Source #

Options for specifying a polygon.

Instances

Instances details
Num n => Default (PolygonOpts n) Source #

The default polygon is a regular pentagon of radius 1, centered at the origin, aligned to the x-axis.

Instance details

Defined in Diagrams.TwoD.Polygons

Methods

def :: PolygonOpts n #

polyType :: Lens' (PolygonOpts n) (PolyType n) Source #

Specification for the polygon's vertices.

polyOrient :: Lens' (PolygonOpts n) (PolyOrientation n) Source #

Should a rotation be applied to the polygon in order to orient it in a particular way?

polyCenter :: Lens' (PolygonOpts n) (Point V2 n) Source #

Should a translation be applied to the polygon in order to place the center at a particular location?

data PolyType n Source #

Method used to determine the vertices of a polygon.

Constructors

PolyPolar [Angle n] [n]

A "polar" polygon.

  • The first argument is a list of central angles from each vertex to the next.
  • The second argument is a list of radii from the origin to each successive vertex.

To construct an n-gon, use a list of n-1 angles and n radii. Extra angles or radii are ignored.

Cyclic polygons (with all vertices lying on a circle) can be constructed using a second argument of (repeat r).

PolySides [Angle n] [n]

A polygon determined by the distance between successive vertices and the external angles formed by each three successive vertices. In other words, a polygon specified by "turtle graphics": go straight ahead x1 units; turn by external angle a1; go straight ahead x2 units; turn by external angle a2; etc. The polygon will be centered at the centroid of its vertices.

  • The first argument is a list of vertex angles, giving the external angle at each vertex from the previous vertex to the next. The first angle in the list is the external angle at the second vertex; the first edge always starts out heading in the positive y direction from the first vertex.
  • The second argument is a list of distances between successive vertices.

To construct an n-gon, use a list of n-2 angles and n-1 edge lengths. Extra angles or lengths are ignored.

PolyRegular Int n

A regular polygon with the given number of sides (first argument) and the given radius (second argument).

data PolyOrientation n Source #

Determine how a polygon should be oriented.

Constructors

NoOrient

No special orientation; the first vertex will be at (1,0).

OrientH

Orient horizontally, so the bottommost edge is parallel to the x-axis. This is the default.

OrientV

Orient vertically, so the leftmost edge is parallel to the y-axis.

OrientTo (V2 n)

Orient so some edge is facing in the direction of, that is, perpendicular to, the given vector.

Star polygons

data StarOpts Source #

Options for creating "star" polygons, where the edges connect possibly non-adjacent vertices.

Constructors

StarFun (Int -> Int)

Specify the order in which the vertices should be connected by a function that maps each vertex index to the index of the vertex that should come next. Indexing of vertices begins at 0.

StarSkip Int

Specify a star polygon by a "skip". A skip of 1 indicates a normal polygon, where edges go between successive vertices. A skip of 2 means that edges will connect every second vertex, skipping one in between. Generally, a skip of n means that edges will connect every nth vertex.

star :: OrderedField n => StarOpts -> [Point V2 n] -> Path V2 n Source #

Create a generalized star polygon. The StarOpts are used to determine in which order the given vertices should be connected. The intention is that the second argument of type [Point v] could be generated by a call to polygon, regPoly, or the like, since a list of vertices is TrailLike. But of course the list can be generated any way you like. A Path v is returned (instead of any TrailLike) because the resulting path may have more than one component, for example if the vertices are to be connected in several disjoint cycles.

Regular polygons

regPoly :: (InSpace V2 n t, TrailLike t) => Int -> n -> t Source #

Create a regular polygon. The first argument is the number of sides, and the second is the length of the sides. (Compare to the polygon function with a PolyRegular option, which produces polygons of a given radius).

The polygon will be oriented with one edge parallel to the x-axis.

triangle :: (InSpace V2 n t, TrailLike t) => n -> t Source #

An equilateral triangle, with sides of the given length and base parallel to the x-axis.

eqTriangle :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A synonym for triangle, provided for backwards compatibility.

square :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A square with its center at the origin and sides of the given length, oriented parallel to the axes.

pentagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular pentagon, with sides of the given length and base parallel to the x-axis.

hexagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular hexagon, with sides of the given length and base parallel to the x-axis.

heptagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular heptagon, with sides of the given length and base parallel to the x-axis.

septagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A synonym for heptagon. It is, however, completely inferior, being a base admixture of the Latin septum (seven) and the Greek γωνία (angle).

octagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular octagon, with sides of the given length and base parallel to the x-axis.

nonagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular nonagon, with sides of the given length and base parallel to the x-axis.

decagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular decagon, with sides of the given length and base parallel to the x-axis.

hendecagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular hendecagon, with sides of the given length and base parallel to the x-axis.

dodecagon :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A regular dodecagon, with sides of the given length and base parallel to the x-axis.

Other special polygons

unitSquare :: (InSpace V2 n t, TrailLike t) => t Source #

A square with its center at the origin and sides of length 1, oriented parallel to the axes.

rect :: (InSpace V2 n t, TrailLike t) => n -> n -> t Source #

rect w h is an axis-aligned rectangle of width w and height h, centered at the origin.

Other shapes

roundedRect :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> n -> t Source #

roundedRect w h r generates a closed trail, or closed path centered at the origin, of an axis-aligned rectangle with width w, height h, and circular rounded corners of radius r. If r is negative the corner will be cut out in a reverse arc. If the size of r is larger than half the smaller dimension of w and h, then it will be reduced to fit in that range, to prevent the corners from overlapping. The trail or path begins with the right edge and proceeds counterclockwise. If you need to specify a different radius for each corner individually, use roundedRect' instead.

roundedRectEx = pad 1.1 . centerXY $ hcat' (with & sep .~ 0.2)
  [ roundedRect  0.5 0.4 0.1
  , roundedRect  0.5 0.4 (-0.1)
  , roundedRect' 0.7 0.4 (with & radiusTL .~ 0.2
                               & radiusTR .~ -0.2
                               & radiusBR .~ 0.1)
  ]

roundedRect' :: (InSpace V2 n t, TrailLike t, RealFloat n) => n -> n -> RoundedRectOpts n -> t Source #

roundedRect' works like roundedRect but allows you to set the radius of each corner indivually, using RoundedRectOpts. The default corner radius is 0. Each radius can also be negative, which results in the curves being reversed to be inward instead of outward.

data RoundedRectOpts d Source #

Constructors

RoundedRectOpts 

Fields

Instances

Instances details
Num d => Default (RoundedRectOpts d) Source # 
Instance details

Defined in Diagrams.TwoD.Shapes

Methods

def :: RoundedRectOpts d #

Arrows

arrowV :: (TypeableFloat n, Renderable (Path V2 n) b) => V2 n -> QDiagram b V2 n Any Source #

arrowV v creates an arrow with the direction and norm of the vector v (with its tail at the origin), using default parameters.

arrowV' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> V2 n -> QDiagram b V2 n Any Source #

arrowV' v creates an arrow with the direction and norm of the vector v (with its tail at the origin).

arrowAt :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> V2 n -> QDiagram b V2 n Any Source #

Create an arrow starting at s with length and direction determined by the vector v.

arrowBetween :: (TypeableFloat n, Renderable (Path V2 n) b) => Point V2 n -> Point V2 n -> QDiagram b V2 n Any Source #

arrowBetween s e creates an arrow pointing from s to e with default parameters.

arrowBetween' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> Point V2 n -> Point V2 n -> QDiagram b V2 n Any Source #

arrowBetween' opts s e creates an arrow pointing from s to e using the given options. In particular, it scales and rotates arrowShaft to go between s and e, taking head, tail, and gaps into account.

connect :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Connect two diagrams with a straight arrow.

connect' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Connect two diagrams with an arbitrary arrow.

connectPerim :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Connect two diagrams at point on the perimeter of the diagrams, choosen by angle.

connectPerim' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> Angle n -> Angle n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

connectOutside :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Draw an arrow from diagram named "n1" to diagram named "n2". The arrow lies on the line between the centres of the diagrams, but is drawn so that it stops at the boundaries of the diagrams, using traces to find the intersection points.

connectOutside' :: (TypeableFloat n, Renderable (Path V2 n) b, IsName n1, IsName n2) => ArrowOpts n -> n1 -> n2 -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

arrow :: (TypeableFloat n, Renderable (Path V2 n) b) => n -> QDiagram b V2 n Any Source #

arrow len creates an arrow of length len with default parameters, starting at the origin and ending at the point (len,0).

arrow' :: (TypeableFloat n, Renderable (Path V2 n) b) => ArrowOpts n -> n -> QDiagram b V2 n Any Source #

arrow' opts len creates an arrow of length len using the given options, starting at the origin and ending at the point (len,0). In particular, it scales the given arrowShaft so that the entire arrow has length len.

straightShaft :: OrderedField n => Trail V2 n Source #

Straight line arrow shaft.

data ArrowOpts n Source #

Instances

Instances details
TypeableFloat n => Default (ArrowOpts n) Source # 
Instance details

Defined in Diagrams.TwoD.Arrow

Methods

def :: ArrowOpts n #

arrowHead :: Lens' (ArrowOpts n) (ArrowHT n) Source #

A shape to place at the head of the arrow.

arrowTail :: Lens' (ArrowOpts n) (ArrowHT n) Source #

A shape to place at the tail of the arrow.

arrowShaft :: Lens' (ArrowOpts n) (Trail V2 n) Source #

The trail to use for the arrow shaft.

headGap :: Lens' (ArrowOpts n) (Measure n) Source #

Distance to leave between the head and the target point.

tailGap :: Lens' (ArrowOpts n) (Measure n) Source #

Distance to leave between the starting point and the tail.

gaps :: Traversal' (ArrowOpts n) (Measure n) Source #

Set both the headGap and tailGap simultaneously.

gap :: Traversal' (ArrowOpts n) (Measure n) Source #

Same as gaps, provided for backward compatiiblity.

headTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source #

A lens for setting or modifying the texture of an arrowhead. For example, one may write ... (with & headTexture .~ grad) to get an arrow with a head filled with a gradient, assuming grad has been defined. Or ... (with & headTexture .~ solid blue to set the head color to blue. For more general control over the style of arrowheads, see headStyle.

headStyle :: Lens' (ArrowOpts n) (Style V2 n) Source #

Style to apply to the head. headStyle is modified by using the lens combinator %~ to change the current style. For example, to change an opaque black arrowhead to translucent orange: (with & headStyle %~ fc orange . opacity 0.75).

tailTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source #

A lens for setting or modifying the texture of an arrow tail. This is *not* a valid lens (see committed).

tailStyle :: Lens' (ArrowOpts n) (Style V2 n) Source #

Style to apply to the tail. See headStyle.

shaftTexture :: TypeableFloat n => Lens' (ArrowOpts n) (Texture n) Source #

A lens for setting or modifying the texture of an arrow shaft.

shaftStyle :: Lens' (ArrowOpts n) (Style V2 n) Source #

Style to apply to the shaft. See headStyle.

headLength :: Lens' (ArrowOpts n) (Measure n) Source #

The length from the start of the joint to the tip of the head.

tailLength :: Lens' (ArrowOpts n) (Measure n) Source #

The length of the tail plus its joint.

lengths :: Traversal' (ArrowOpts n) (Measure n) Source #

Set both the headLength and tailLength simultaneously.

Text

text :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, with center alignment, equivalent to alignedText 0.5 0.5.

Note that it takes up no space, as text size information is not available.

topLeftText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, origin at the top left corner of the text's bounding box, equivalent to alignedText 0 1.

Note that it takes up no space.

alignedText :: (TypeableFloat n, Renderable (Text n) b) => n -> n -> String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, with the origin set to a point interpolated within the bounding box. The first parameter varies from 0 (left) to 1 (right), and the second parameter from 0 (bottom) to 1 (top). Some backends do not implement this and instead snap to closest corner or the center.

The height of this box is determined by the font's potential ascent and descent, rather than the height of the particular string.

Note that it takes up no space.

baselineText :: (TypeableFloat n, Renderable (Text n) b) => String -> QDiagram b V2 n Any Source #

Create a primitive text diagram from the given string, with the origin set to be on the baseline, at the beginning (although not bounding). This is the reference point of showText in the Cairo graphics library.

Note that it takes up no space.

font :: HasStyle a => String -> a -> a Source #

Specify a font family to be used for all text within a diagram.

italic :: HasStyle a => a -> a Source #

Set all text in italics.

oblique :: HasStyle a => a -> a Source #

Set all text using an oblique slant.

fontSize :: (N a ~ n, Typeable n, HasStyle a) => Measure n -> a -> a Source #

Set the font size, that is, the size of the font's em-square as measured within the current local vector space. The default size is local 1 (which is applied by recommendFontSize).

bold :: HasStyle a => a -> a Source #

Set all text using a bold font weight.

bolder :: HasStyle a => a -> a Source #

Set all text to be bolder than the inherited font weight.

lighter :: HasStyle a => a -> a Source #

Set all text to be lighter than the inherited font weight.

thinWeight :: HasStyle a => a -> a Source #

Set all text using a thin font weight.

ultraLight :: HasStyle a => a -> a Source #

Set all text using a extra light font weight.

light :: HasStyle a => a -> a Source #

Set all text using a light font weight.

mediumWeight :: HasStyle a => a -> a Source #

Set all text using a medium font weight.

heavy :: HasStyle a => a -> a Source #

Set all text using a heavy/black font weight.

semiBold :: HasStyle a => a -> a Source #

Set all text using a semi-bold font weight.

ultraBold :: HasStyle a => a -> a Source #

Set all text using an ultra-bold font weight.

_font :: Lens' (Style v n) (Maybe String) Source #

Lens onto the font name of a style.

_fontSize :: (Typeable n, OrderedField n) => Lens' (Style v n) (Measure n) Source #

Lens to commit a font size. This is *not* a valid lens (see commited.

fontSizeO :: (N a ~ n, Typeable n, HasStyle a) => n -> a -> a Source #

A convenient synonym for 'fontSize (Output w)'.

fontSizeL :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source #

A convenient sysnonym for 'fontSize (Local w)'.

fontSizeN :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source #

A convenient synonym for 'fontSize (Normalized w)'.

fontSizeG :: (N a ~ n, Typeable n, Num n, HasStyle a) => n -> a -> a Source #

A convenient synonym for 'fontSize (Global w)'.

Images

data DImage :: Type -> Type -> Type where Source #

An image primitive, the two ints are width followed by height. Will typically be created by loadImageEmb or loadImageExt which, will handle setting the width and height to the actual width and height of the image.

Constructors

DImage :: ImageData t -> Int -> Int -> Transformation V2 n -> DImage n t 

Instances

Instances details
Fractional n => HasOrigin (DImage n a) Source # 
Instance details

Defined in Diagrams.TwoD.Image

Methods

moveOriginTo :: Point (V (DImage n a)) (N (DImage n a)) -> DImage n a -> DImage n a #

Fractional n => Transformable (DImage n a) Source # 
Instance details

Defined in Diagrams.TwoD.Image

Methods

transform :: Transformation (V (DImage n a)) (N (DImage n a)) -> DImage n a -> DImage n a #

Fractional n => Renderable (DImage n a) NullBackend Source # 
Instance details

Defined in Diagrams.TwoD.Image

Methods

render :: NullBackend -> DImage n a -> Render NullBackend (V (DImage n a)) (N (DImage n a)) #

RealFloat n => HasQuery (DImage n a) Any Source # 
Instance details

Defined in Diagrams.TwoD.Image

Methods

getQuery :: DImage n a -> Query (V (DImage n a)) (N (DImage n a)) Any Source #

type N (DImage n a) Source # 
Instance details

Defined in Diagrams.TwoD.Image

type N (DImage n a) = n
type V (DImage n a) Source # 
Instance details

Defined in Diagrams.TwoD.Image

type V (DImage n a) = V2

data ImageData :: Type -> Type where Source #

ImageData is either a JuicyPixels DynamicImage tagged as Embedded or a reference tagged as External. Additionally Native is provided for external libraries to hook into.

data Native (t :: Type) Source #

image :: (TypeableFloat n, Typeable a, Renderable (DImage n a) b) => DImage n a -> QDiagram b V2 n Any Source #

Make a DImage into a Diagram.

loadImageEmb :: Num n => FilePath -> IO (Either String (DImage n Embedded)) Source #

Use JuicyPixels to read a file in any format and wrap it in a DImage. The width and height of the image are set to their actual values.

loadImageExt :: Num n => FilePath -> IO (Either String (DImage n External)) Source #

Check that a file exists, and use JuicyPixels to figure out the right size, but save a reference to the image instead of the raster data

uncheckedImageRef :: Num n => FilePath -> Int -> Int -> DImage n External Source #

Make an "unchecked" image reference; have to specify a width and height. Unless the aspect ratio of the external image is the w :: h, then the image will be distorted.

raster :: Num n => (Int -> Int -> AlphaColour Double) -> Int -> Int -> DImage n Embedded Source #

Create an image "from scratch" by specifying the pixel data

rasterDia :: (TypeableFloat n, Renderable (DImage n Embedded) b) => (Int -> Int -> AlphaColour Double) -> Int -> Int -> QDiagram b V2 n Any Source #

Crate a diagram from raw raster data.

Transformations

Rotation

rotation :: Floating n => Angle n -> Transformation V2 n Source #

Create a transformation which performs a rotation about the local origin by the given angle. See also rotate.

rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t Source #

Rotate about the local origin by the given angle. Positive angles correspond to counterclockwise rotation, negative to clockwise. The angle can be expressed using any of the Isos on Angle. For example, rotate (1/4 @@ turn), rotate (tau/4 @@ rad), and rotate (90 @@ deg) all represent the same transformation, namely, a counterclockwise rotation by a right angle. To rotate about some point other than the local origin, see rotateAbout.

Note that writing rotate (1/4), with no Angle constructor, will yield an error since GHC cannot figure out which sort of angle you want to use. In this common situation you can use rotateBy, which interprets its argument as a number of turns.

rotateBy :: (InSpace V2 n t, Transformable t, Floating n) => n -> t -> t Source #

A synonym for rotate, interpreting its argument in units of turns; it can be more convenient to write rotateBy (1/4) than rotate (1/4 @@ turn).

rotated :: (InSpace V2 n a, Floating n, SameSpace a b, Transformable a, Transformable b) => Angle n -> Iso a b a b Source #

Use an Angle to make an Iso between an object rotated and unrotated. This us useful for performing actions under a rotation:

under (rotated t) f = rotate (negated t) . f . rotate t
rotated t ## a      = rotate t a
a ^. rotated t      = rotate (-t) a
over (rotated t) f  = rotate t . f . rotate (negated t)

rotationAround :: Floating n => P2 n -> Angle n -> T2 n Source #

rotationAbout p is a rotation about the point p (instead of around the local origin).

rotateAround :: (InSpace V2 n t, Transformable t, Floating n) => P2 n -> Angle n -> t -> t Source #

rotateAbout p is like rotate, except it rotates around the point p instead of around the local origin.

rotationTo :: OrderedField n => Direction V2 n -> T2 n Source #

The rotation that aligns the x-axis with the given direction.

rotateTo :: (InSpace V2 n t, OrderedField n, Transformable t) => Direction V2 n -> t -> t Source #

Rotate around the local origin such that the x axis aligns with the given direction.

Scaling

scalingX :: (Additive v, R1 v, Fractional n) => n -> Transformation v n Source #

Construct a transformation which scales by the given factor in the x (horizontal) direction.

scaleX :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t Source #

Scale a diagram by the given factor in the x (horizontal) direction. To scale uniformly, use scale.

scalingY :: (Additive v, R2 v, Fractional n) => n -> Transformation v n Source #

Construct a transformation which scales by the given factor in the y (vertical) direction.

scaleY :: (InSpace v n t, R2 v, Fractional n, Transformable t) => n -> t -> t Source #

Scale a diagram by the given factor in the y (vertical) direction. To scale uniformly, use scale.

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

Create a uniform scaling transformation.

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

Scale uniformly in every dimension by the given scalar.

scaleToX :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleToX w scales a diagram in the x (horizontal) direction by whatever factor required to make its width w. scaleToX should not be applied to diagrams with a width of 0, such as vrule.

scaleToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleToY h scales a diagram in the y (vertical) direction by whatever factor required to make its height h. scaleToY should not be applied to diagrams with a height of 0, such as hrule.

scaleUToX :: (InSpace v n t, R1 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleUToX w scales a diagram uniformly by whatever factor required to make its width w. scaleUToX should not be applied to diagrams with a width of 0, such as vrule.

scaleUToY :: (InSpace v n t, R2 v, Enveloped t, Transformable t) => n -> t -> t Source #

scaleUToY h scales a diagram uniformly by whatever factor required to make its height h. scaleUToY should not be applied to diagrams with a height of 0, such as hrule.

Translation

translationX :: (Additive v, R1 v, Num n) => n -> Transformation v n Source #

Construct a transformation which translates by the given distance in the x (horizontal) direction.

translateX :: (InSpace v n t, R1 v, Transformable t) => n -> t -> t Source #

Translate a diagram by the given distance in the x (horizontal) direction.

translationY :: (Additive v, R2 v, Num n) => n -> Transformation v n Source #

Construct a transformation which translates by the given distance in the y (vertical) direction.

translateY :: (InSpace v n t, R2 v, Transformable t) => n -> t -> t Source #

Translate a diagram by the given distance in the y (vertical) direction.

translation :: v n -> Transformation v n #

Create a translation.

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

Translate by a vector.

Conformal affine maps

scalingRotationTo :: Floating n => V2 n -> T2 n Source #

The angle-preserving linear map that aligns the x-axis unit vector with the given vector. See also scaleRotateTo.

scaleRotateTo :: (InSpace V2 n t, Transformable t, Floating n) => V2 n -> t -> t Source #

Rotate and uniformly scale around the local origin such that the x-axis aligns with the given vector. This satisfies the equation

scaleRotateTo v = rotateTo (dir v) . scale (norm v)

up to floating point rounding errors, but is more accurate and performant since it avoids cancellable uses of trigonometric functions.

Reflection

reflectionX :: (Additive v, R1 v, Num n) => Transformation v n Source #

Construct a transformation which flips a diagram from left to right, i.e. sends the point (x,y) to (-x,y).

reflectX :: (InSpace v n t, R1 v, Transformable t) => t -> t Source #

Flip a diagram from left to right, i.e. send the point (x,y) to (-x,y).

reflectionY :: (Additive v, R2 v, Num n) => Transformation v n Source #

Construct a transformation which flips a diagram from top to bottom, i.e. sends the point (x,y) to (x,-y).

reflectY :: (InSpace v n t, R2 v, Transformable t) => t -> t Source #

Flip a diagram from top to bottom, i.e. send the point (x,y) to (x,-y).

reflectionXY :: (Additive v, R2 v, Num n) => Transformation v n Source #

Construct a transformation which flips the diagram about x=y, i.e. sends the point (x,y) to (y,x).

reflectXY :: (InSpace v n t, R2 v, Transformable t) => t -> t Source #

Flips the diagram about x=y, i.e. send the point (x,y) to (y,x).

reflectionAbout :: OrderedField n => P2 n -> Direction V2 n -> T2 n Source #

reflectionAbout p d is a reflection in the line determined by the point p and direction d.

reflectAbout :: (InSpace V2 n t, OrderedField n, Transformable t) => P2 n -> Direction V2 n -> t -> t Source #

reflectAbout p d reflects a diagram in the line determined by the point p and direction d.

Shears

shearingX :: Num n => n -> T2 n Source #

shearingX d is the linear transformation which is the identity on y coordinates and sends (0,1) to (d,1).

shearX :: (InSpace V2 n t, Transformable t) => n -> t -> t Source #

shearX d performs a shear in the x-direction which sends (0,1) to (d,1).

shearingY :: Num n => n -> T2 n Source #

shearingY d is the linear transformation which is the identity on x coordinates and sends (1,0) to (1,d).

shearY :: (InSpace V2 n t, Transformable t) => n -> t -> t Source #

shearY d performs a shear in the y-direction which sends (1,0) to (1,d).

Deformations - non-affine transforms

parallelX0 :: (R1 v, Num n) => Deformation v v n Source #

The parallel projection onto the plane x=0

perspectiveX1 :: (R1 v, Functor v, Fractional n) => Deformation v v n Source #

The perspective division onto the plane x=1 along lines going through the origin.

parallelY0 :: (R2 v, Num n) => Deformation v v n Source #

The parallel projection onto the plane y=0

perspectiveY1 :: (R2 v, Functor v, Floating n) => Deformation v v n Source #

The perspective division onto the plane y=1 along lines going through the origin.

facingX :: (R1 v, Functor v, Fractional n) => Deformation v v n Source #

The viewing transform for a viewer facing along the positive X axis. X coördinates stay fixed, while Y coördinates are compressed with increasing distance. asDeformation (translation unitX) <> parallelX0 <> frustrumX = perspectiveX1

Combinators

Combining multiple diagrams

(===) :: (InSpace V2 n a, Juxtaposable a, Semigroup a) => a -> a -> a infixl 6 Source #

Place two diagrams (or other objects) vertically adjacent to one another, with the first diagram above the second. Since Haskell ignores whitespace in expressions, one can thus write

      c
     ===
      d
  

to place c above d. The local origin of the resulting combined diagram is the same as the local origin of the first. (===) is associative and has mempty as an identity. See the documentation of beside for more information.

(|||) :: (InSpace V2 n a, Juxtaposable a, Semigroup a) => a -> a -> a infixl 6 Source #

Place two diagrams (or other juxtaposable objects) horizontally adjacent to one another, with the first diagram to the left of the second. The local origin of the resulting combined diagram is the same as the local origin of the first. (|||) is associative and has mempty as an identity. See the documentation of beside for more information.

hcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a Source #

Lay out a list of juxtaposable objects in a row from left to right, so that their local origins lie along a single horizontal line, with successive envelopes tangent to one another.

  • For more control over the spacing, see hcat'.
  • To align the diagrams vertically (or otherwise), use alignment combinators (such as alignT or alignB) from Diagrams.TwoD.Align before applying hcat.
  • For non-axis-aligned layout, see cat.

hcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a Source #

A variant of hcat taking an extra CatOpts record to control the spacing. See the cat' documentation for a description of the possibilities. For the common case of setting just a separation amount, see hsep.

hsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a Source #

A convenient synonym for horizontal concatenation with separation: hsep s === hcat' (with & sep .~ s).

vcat :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => [a] -> a Source #

Lay out a list of juxtaposable objects in a column from top to bottom, so that their local origins lie along a single vertical line, with successive envelopes tangent to one another.

  • For more control over the spacing, see vcat'.
  • To align the diagrams horizontally (or otherwise), use alignment combinators (such as alignL or alignR) from Diagrams.TwoD.Align before applying vcat.
  • For non-axis-aligned layout, see cat.

vcat' :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => CatOpts n -> [a] -> a Source #

A variant of vcat taking an extra CatOpts record to control the spacing. See the cat' documentation for a description of the possibilities. For the common case of setting just a separation amount, see vsep.

vsep :: (InSpace V2 n a, Floating n, Juxtaposable a, HasOrigin a, Monoid' a) => n -> [a] -> a Source #

A convenient synonym for vertical concatenation with separation: vsep s === vcat' (with & sep .~ s).

Spacing and envelopes

strutX :: (Metric v, R1 v, OrderedField n) => n -> QDiagram b v n m Source #

strutX w is an empty diagram with width w, height 0, and a centered local origin. Note that strutX (-w) behaves the same as strutX w.

strutY :: (Metric v, R2 v, OrderedField n) => n -> QDiagram b v n m Source #

strutY h is an empty diagram with height h, width 0, and a centered local origin. Note that strutY (-h) behaves the same as strutY h.

padX :: (Metric v, R2 v, OrderedField n, Monoid' m) => n -> QDiagram b v n m -> QDiagram b v n m Source #

padX s "pads" a diagram in the x-direction, expanding its envelope horizontally by a factor of s (factors between 0 and 1 can be used to shrink the envelope). Note that the envelope will expand with respect to the local origin, so if the origin is not centered horizontally the padding may appear "uneven". If this is not desired, the origin can be centered (using centerX) before applying padX.

padY :: (Metric v, R2 v, Monoid' m, OrderedField n) => n -> QDiagram b v n m -> QDiagram b v n m Source #

padY s "pads" a diagram in the y-direction, expanding its envelope vertically by a factor of s (factors between 0 and 1 can be used to shrink the envelope). Note that the envelope will expand with respect to the local origin, so if the origin is not centered vertically the padding may appear "uneven". If this is not desired, the origin can be centered (using centerY) before applying padY.

extrudeLeft :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

extrudeLeft s "extrudes" a diagram in the negative x-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

extrudeRight :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

extrudeRight s "extrudes" a diagram in the positive x-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

extrudeBottom :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

extrudeBottom s "extrudes" a diagram in the negative y-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

extrudeTop :: (OrderedField n, Monoid' m) => n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

extrudeTop s "extrudes" a diagram in the positive y-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

rectEnvelope :: forall b n m. (OrderedField n, Monoid' m) => Point V2 n -> V2 n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

rectEnvelope p v sets the envelope of a diagram to a rectangle whose lower-left corner is at p and whose upper-right corner is at p .+^ v. Useful for selecting the rectangular portion of a diagram which should actually be "viewed" in the final render, if you don't want to see the entire diagram.

crop :: forall b n m. (OrderedField n, Monoid' m) => Point V2 n -> V2 n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

A synonym for rectEnvelope.

Background

boundingRect :: (InSpace V2 n a, SameSpace a t, Enveloped t, Transformable t, TrailLike t, Monoid t, Enveloped a) => a -> t Source #

Construct a bounding rectangle for an enveloped object, that is, the smallest axis-aligned rectangle which encloses the object.

bg :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' q) => Colour Double -> QDiagram b V2 n q -> QDiagram b V2 n q Source #

"Set the background color" of a diagram. That is, place a diagram atop a bounding rectangle of the given color. The background does not change the result of queries.

bgFrame :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' q) => n -> Colour Double -> QDiagram b V2 n q -> QDiagram b V2 n q Source #

Similar to bg but makes the colored background rectangle larger than the diagram. The first parameter is used to set how far the background extends beyond the diagram. The background does not change the result of queries.

Alignment

alignL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Align along the left edge, i.e. translate the diagram in a horizontal direction so that the local origin is on the left edge of the envelope.

alignR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Align along the right edge.

alignT :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Align along the top edge.

alignB :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Align along the bottom edge.

alignTL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

alignTR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

alignBL :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

alignBR :: (InSpace V2 n a, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

alignX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a Source #

alignX and snugX move the local origin horizontally as follows:

  • alignX (-1) moves the local origin to the left edge of the boundary;
  • align 1 moves the local origin to the right edge;
  • any other argument interpolates linearly between these. For example, alignX 0 centers, alignX 2 moves the origin one "radius" to the right of the right edge, and so on.
  • snugX works the same way.

alignY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => n -> a -> a Source #

Like alignX, but moving the local origin vertically, with an argument of 1 corresponding to the top edge and (-1) corresponding to the bottom edge.

centerX :: (InSpace v n a, R1 v, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Center the local origin along the X-axis.

centerY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Center the local origin along the Y-axis.

centerXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, HasOrigin a) => a -> a Source #

Center along both the X- and Y-axes.

Snugging

snugL :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

snugR :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

snugT :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

snugB :: (InSpace V2 n a, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

snugX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a Source #

See the documentation for alignX.

snugY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => n -> a -> a Source #

See the documentation for alignY.

snugCenterX :: (InSpace v n a, R1 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

snugCenterY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

snugCenterXY :: (InSpace v n a, R2 v, Fractional n, Alignable a, Traced a, HasOrigin a) => a -> a Source #

Size

Computing size

width :: (InSpace V2 n a, Enveloped a) => a -> n Source #

Compute the width of an enveloped object.

Note this is just diameter unitX.

height :: (InSpace V2 n a, Enveloped a) => a -> n Source #

Compute the height of an enveloped object.

extentX :: (InSpace v n a, R1 v, Enveloped a) => a -> Maybe (n, n) Source #

Compute the absolute x-coordinate range of an enveloped object in the form (lo,hi). Return Nothing for objects with an empty envelope.

Note this is just extent unitX.

extentY :: (InSpace v n a, R2 v, Enveloped a) => a -> Maybe (n, n) Source #

Compute the absolute y-coordinate range of an enveloped object in the form (lo,hi). Return Nothing for objects with an empty envelope.

Specifying size

mkSizeSpec2D :: Num n => Maybe n -> Maybe n -> SizeSpec V2 n Source #

Make a SizeSpec from possibly-specified width and height.

mkWidth :: Num n => n -> SizeSpec V2 n Source #

Make a SizeSpec with only width defined.

mkHeight :: Num n => n -> SizeSpec V2 n Source #

Make a SizeSpec with only height defined.

dims2D :: n -> n -> SizeSpec V2 n Source #

Make a SizeSpec from a width and height.

Textures

data Texture n Source #

A Texture is either a color SC, linear gradient LG, or radial gradient RG. An object can have only one texture which is determined by the Last semigroup structure.

Constructors

SC SomeColor 
LG (LGradient n) 
RG (RGradient n) 

Instances

Instances details
Floating n => Transformable (Texture n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

Methods

transform :: Transformation (V (Texture n)) (N (Texture n)) -> Texture n -> Texture n #

type N (Texture n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type N (Texture n) = n
type V (Texture n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type V (Texture n) = V2

solid :: Color a => a -> Texture n Source #

Convert a solid colour into a texture.

data SpreadMethod Source #

The SpreadMethod determines what happens before lGradStart and after lGradEnd. GradPad fills the space before the start of the gradient with the color of the first stop and the color after end of the gradient with the color of the last stop. GradRepeat restarts the gradient and GradReflect restarts the gradient with the stops in reverse order.

data GradientStop d Source #

A gradient stop contains a color and fraction (usually between 0 and 1)

Constructors

GradientStop 

fillTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a Source #

_fillTexture :: (Typeable n, Floating n) => Lens' (Style V2 n) (Texture n) Source #

Commit a fill texture in a style. This is not a valid setter because it doesn't abide the functor law (see committed).

lineTexture :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Texture n -> a -> a Source #

stopFraction :: Lens' (GradientStop n) n Source #

The fraction for stop.

stopColor :: Lens' (GradientStop n) SomeColor Source #

A color for the stop.

mkStops :: [(Colour Double, d, Double)] -> [GradientStop d] Source #

A convenient function for making gradient stops from a list of triples. (An opaque color, a stop fraction, an opacity).

data LGradient n Source #

Linear Gradient

Instances

Instances details
Fractional n => Transformable (LGradient n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type N (LGradient n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type N (LGradient n) = n
type V (LGradient n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type V (LGradient n) = V2

_LG :: forall n. Prism' (Texture n) (LGradient n) Source #

lGradStops :: Lens' (LGradient n) [GradientStop n] Source #

A list of stops (colors and fractions).

lGradTrans :: Lens' (LGradient n) (Transformation V2 n) Source #

A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.

lGradStart :: Lens' (LGradient n) (Point V2 n) Source #

The starting point for the first gradient stop. The coordinates are in local units and the default is (-0.5, 0).

lGradEnd :: Lens' (LGradient n) (Point V2 n) Source #

The ending point for the last gradient stop.The coordinates are in local units and the default is (0.5, 0).

lGradSpreadMethod :: Lens' (LGradient n) SpreadMethod Source #

For setting the spread method.

defaultLG :: Fractional n => Texture n Source #

A default is provided so that linear gradients can easily be created using lenses. For example, lg = defaultLG & lGradStart .~ (0.25 ^& 0.33). Note that no default value is provided for lGradStops, this must be set before the gradient value is used, otherwise the object will appear transparent.

mkLinearGradient :: Num n => [GradientStop n] -> Point V2 n -> Point V2 n -> SpreadMethod -> Texture n Source #

Make a linear gradient texture from a stop list, start point, end point, and SpreadMethod. The lGradTrans field is set to the identity transfrom, to change it use the lGradTrans lens.

data RGradient n Source #

Radial Gradient

Instances

Instances details
Fractional n => Transformable (RGradient n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type N (RGradient n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type N (RGradient n) = n
type V (RGradient n) Source # 
Instance details

Defined in Diagrams.TwoD.Attributes

type V (RGradient n) = V2

rGradStops :: Lens' (RGradient n) [GradientStop n] Source #

A list of stops (colors and fractions).

rGradCenter0 :: Lens' (RGradient n) (Point V2 n) Source #

The center point of the inner circle.

rGradRadius0 :: Lens' (RGradient n) n Source #

The radius of the inner cirlce in local coordinates.

rGradCenter1 :: Lens' (RGradient n) (Point V2 n) Source #

The center of the outer circle.

rGradRadius1 :: Lens' (RGradient n) n Source #

The radius of the outer circle in local coordinates.

rGradTrans :: Lens' (RGradient n) (Transformation V2 n) Source #

A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.

rGradSpreadMethod :: Lens' (RGradient n) SpreadMethod Source #

For setting the spread method.

defaultRG :: Fractional n => Texture n Source #

A default is provided so that radial gradients can easily be created using lenses. For example, rg = defaultRG & rGradRadius1 .~ 0.25. Note that no default value is provided for rGradStops, this must be set before the gradient value is used, otherwise the object will appear transparent.

_RG :: forall n. Prism' (Texture n) (RGradient n) Source #

mkRadialGradient :: Num n => [GradientStop n] -> Point V2 n -> n -> Point V2 n -> n -> SpreadMethod -> Texture n Source #

Make a radial gradient texture from a stop list, radius, start point, end point, and SpreadMethod. The rGradTrans field is set to the identity transfrom, to change it use the rGradTrans lens.

Colors

fillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source #

Set the fill color. This function is polymorphic in the color type (so it can be used with either Colour or AlphaColour), but this can sometimes create problems for type inference, so the fc and fcA variants are provided with more concrete types.

_SC :: forall n. Prism' (Texture n) SomeColor Source #

_AC :: Prism' (Texture n) (AlphaColour Double) Source #

Prism onto an AlphaColour Double of a SC texture.

fc :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => Colour Double -> a -> a Source #

A synonym for fillColor, specialized to Colour Double (i.e. opaque colors). See comment after fillColor about backends.

fcA :: (InSpace V2 n a, Floating n, Typeable n, HasStyle a) => AlphaColour Double -> a -> a Source #

A synonym for fillColor, specialized to AlphaColour Double (i.e. colors with transparency). See comment after fillColor about backends.

recommendFillColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source #

Set a "recommended" fill color, to be used only if no explicit calls to fillColor (or fc, or fcA) are used. See comment after fillColor about backends.

lineColor :: (InSpace V2 n a, Color c, Typeable n, Floating n, HasStyle a) => c -> a -> a Source #

Set the line (stroke) color. This function is polymorphic in the color type (so it can be used with either Colour or AlphaColour), but this can sometimes create problems for type inference, so the lc and lcA variants are provided with more concrete types.

lc :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => Colour Double -> a -> a Source #

A synonym for lineColor, specialized to Colour Double (i.e. opaque colors). See comment in lineColor about backends.

lcA :: (InSpace V2 n a, Typeable n, Floating n, HasStyle a) => AlphaColour Double -> a -> a Source #

A synonym for lineColor, specialized to AlphaColour Double (i.e. colors with transparency). See comment in lineColor about backends.

Visual aids for understanding the internal model

showOrigin :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => QDiagram b V2 n m -> QDiagram b V2 n m Source #

Mark the origin of a diagram by placing a red dot 1/50th its size.

showOrigin' :: (TypeableFloat n, Renderable (Path V2 n) b, Monoid' m) => OriginOpts n -> QDiagram b V2 n m -> QDiagram b V2 n m Source #

Mark the origin of a diagram, with control over colour and scale of marker dot.

data OriginOpts n Source #

Constructors

OriginOpts 

Fields

Instances

Instances details
Fractional n => Default (OriginOpts n) Source # 
Instance details

Defined in Diagrams.TwoD.Model

Methods

def :: OriginOpts n #

oScale :: forall n. Lens' (OriginOpts n) n Source #

oMinSize :: forall n. Lens' (OriginOpts n) n Source #

showEnvelope :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Mark the envelope with an approximating cubic spline using 32 points, medium line width and red line color.

showEnvelope' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => EnvelopeOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Mark the envelope with an approximating cubic spline with control over the color, line width and number of points.

data EnvelopeOpts n Source #

Constructors

EnvelopeOpts 

Instances

Instances details
OrderedField n => Default (EnvelopeOpts n) Source # 
Instance details

Defined in Diagrams.TwoD.Model

Methods

def :: EnvelopeOpts n #

showTrace :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Mark the trace of a diagram by placing 64 red dots 1/100th its size along the trace.

showTrace' :: (Enum n, TypeableFloat n, Renderable (Path V2 n) b) => TraceOpts n -> QDiagram b V2 n Any -> QDiagram b V2 n Any Source #

Mark the trace of a diagram, with control over colour and scale of marker dot and the number of points on the trace.

data TraceOpts n Source #

Constructors

TraceOpts 

Fields

Instances

Instances details
Floating n => Default (TraceOpts n) Source # 
Instance details

Defined in Diagrams.TwoD.Model

Methods

def :: TraceOpts n #

tScale :: forall n. Lens' (TraceOpts n) n Source #

tMinSize :: forall n. Lens' (TraceOpts n) n Source #

tPoints :: forall n. Lens' (TraceOpts n) Int Source #