diagrams-lib-1.4.3: Embedded domain-specific language for declarative graphics

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

Diagrams.Points

Contents

Description

Points in space. For more tools for working with points and vectors, see Linear.Affine.

Synopsis

Points

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

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

Constructors

P (f a) 
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) #

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 #

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) #

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 #

Hashable1 f => Hashable1 (Point f) 
Instance details

Defined in Linear.Affine

Methods

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

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 #

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 #

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

Defined in Diagrams.Angle

Methods

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

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

Defined in Diagrams.Angle

Methods

_theta :: RealFloat n => Lens' (Point v n) (Angle 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 #

(Metric v, OrderedField n) => TrailLike [Point v n] Source #

A list of points is trail-like; this instance simply computes the vertices of the trail, using trailPoints.

Instance details

Defined in Diagrams.TrailLike

Methods

trailLike :: Located (Trail (V [Point v n]) (N [Point v n])) -> [Point v n] Source #

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 -> () #

(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)) #

(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, 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, 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 #

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 #

Coordinates (v n) => Coordinates (Point v n) Source # 
Instance details

Defined in Diagrams.Coordinates

Associated Types

type FinalCoord (Point v n) :: Type Source #

type PrevDim (Point v n) :: Type Source #

type Decomposition (Point v n) :: Type Source #

Methods

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

pr :: PrevDim (Point v n) -> FinalCoord (Point v n) -> Point v n Source #

coords :: Point v n -> Decomposition (Point v n) Source #

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

Defined in Linear.Affine

(Additive v, Num n, r ~ Point u n) => AffineMappable (Point v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

amap :: AffineMap (V (Point v n)) (V r) (N r) -> Point v n -> r Source #

r ~ Point u n => Deformable (Point v n) r Source # 
Instance details

Defined in Diagrams.Deform

Methods

deform' :: N (Point v n) -> Deformation (V (Point v n)) (V r) (N (Point v n)) -> Point v n -> r Source #

deform :: Deformation (V (Point v n)) (V r) (N (Point v n)) -> Point v n -> r Source #

LinearMappable (Point v n) (Point u m) Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

vmap :: (Vn (Point v n) -> Vn (Point u m)) -> Point v n -> Point u m Source #

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 #

Each (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') Source # 
Instance details

Defined in Diagrams.Segment

Methods

each :: Traversal (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') #

(Additive v', Foldable v', Ord n') => Each (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') Source #

Only valid if the second point is not smaller than the first.

Instance details

Defined in Diagrams.BoundingBox

Methods

each :: Traversal (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') #

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.9-FQ1kq2xAlAxC2ls6AC0YzF" 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.9-FQ1kq2xAlAxC2ls6AC0YzF" True) (C1 (MetaCons "P" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))
type V (Point v n) 
Instance details

Defined in Diagrams.Core.Points

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

Defined in Diagrams.Core.Points

type N (Point v n) = n
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 FinalCoord (Point v n) Source # 
Instance details

Defined in Diagrams.Coordinates

type FinalCoord (Point v n) = FinalCoord (v n)
type PrevDim (Point v n) Source # 
Instance details

Defined in Diagrams.Coordinates

type PrevDim (Point v n) = PrevDim (v n)
type Decomposition (Point v n) Source # 
Instance details

Defined in Diagrams.Coordinates

type Decomposition (Point v n) = Decomposition (v n)

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 '(*^)'.

Point-related utilities

centroid :: (Additive v, Fractional n) => [Point v n] -> Point v n Source #

The centroid of a set of n points is their sum divided by n. Returns the origin for an empty list of points.

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.

_Point :: Iso' (Point f a) (f a) #

lensP :: Lens' (Point g a) (g a) #