diagrams-core-1.4: Core libraries for diagrams EDSL

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

Diagrams.Core.Points

Contents

Description

A type for points (as distinct from vectors).

Synopsis

Points

newtype Point f 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) 

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) 

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) 

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) 

Methods

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

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

Applicative f => Applicative (Point f) 

Methods

pure :: a -> Point f a #

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

Foldable f => Foldable (Point f) 

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) 

Methods

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

sequenceA :: Applicative f => Point f (f a) -> f (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) #

Generic1 (Point f) 

Associated Types

type Rep1 (Point f :: * -> *) :: * -> * #

Methods

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

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

Distributive f => Distributive (Point f) 

Methods

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

collect :: Functor f => (a -> Point f b) -> f a -> Point f (f 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) 

Associated Types

type Rep (Point f :: * -> *) :: * #

Methods

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

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

Eq1 f => Eq1 (Point f) 

Methods

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

Ord1 f => Ord1 (Point f) 

Methods

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

Read1 f => Read1 (Point f) 

Methods

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

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

Show1 f => Show1 (Point f) 

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) 

Methods

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

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

Additive f => Affine (Point f) 

Associated Types

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

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) 

Methods

_w :: Functor f => (a -> f a) -> Point f a -> f (Point f a) #

_xyzw :: Functor f => (V4 a -> f (V4 a)) -> Point f a -> f (Point f a) #

R3 f => R3 (Point f) 

Methods

_z :: Functor f => (a -> f a) -> Point f a -> f (Point f a) #

_xyz :: Functor f => (V3 a -> f (V3 a)) -> Point f a -> f (Point f a) #

R2 f => R2 (Point f) 

Methods

_y :: Functor f => (a -> f a) -> Point f a -> f (Point f a) #

_xy :: Functor f => (V2 a -> f (V2 a)) -> Point f a -> f (Point f a) #

R1 f => R1 (Point f) 

Methods

_x :: Functor f => (a -> f a) -> Point f a -> f (Point f a) #

Metric f => Metric (Point f) 

Methods

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

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

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

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

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

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

Additive f => Additive (Point f) 

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 #

Apply f => Apply (Point f) 

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 #

Bind f => Bind (Point f) 

Methods

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

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

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

Methods

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

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

Methods

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

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

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

Methods

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

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

fromRational :: Rational -> Point f a #

(Data (f a), Typeable * a, Typeable (* -> *) f) => Data (Point f a) 

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) 

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) 

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) 
Show (f a) => Show (Point f a) 

Methods

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

show :: Point f a -> String #

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

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

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) 

Associated Types

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

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) 

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) 

Methods

put :: Point f a -> Put #

get :: Get (Point f a) #

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

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

Methods

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

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

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

Methods

put :: Putter (Point f a) #

get :: Get (Point f a) #

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

Methods

rnf :: Point f a -> () #

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

Methods

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

hash :: Point f a -> Int #

Unbox (f a) => Unbox (Point f a) 
Ixed (f a) => Ixed (Point f a) 

Methods

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

Wrapped (Point f a) 

Associated Types

type Unwrapped (Point f a) :: * #

Methods

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

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

Methods

nearZero :: Point f a -> Bool #

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

Methods

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

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

Methods

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

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

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

Methods

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

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

Methods

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

(~) * t (Point g b) => Rewrapped (Point f a) t 
Traversable f => Each (Point f a) (Point f b) a b 

Methods

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

data MVector s (Point f a) 
data MVector s (Point f a) = MV_P ~(MVector s (f a))
type Rep1 (Point f) 
type Rep1 (Point f) = D1 (MetaData "Point" "Linear.Affine" "linear-1.20.5-ALqHTYew01KD1PdDd6TYmz" True) (C1 (MetaCons "P" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (Point f) 
type Rep (Point f) = Rep f
type Diff (Point f) 
type Diff (Point f) = f
type Rep (Point f a) 
type Rep (Point f a) = D1 (MetaData "Point" "Linear.Affine" "linear-1.20.5-ALqHTYew01KD1PdDd6TYmz" True) (C1 (MetaCons "P" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))
data Vector (Point f a) 
data Vector (Point f a) = V_P ~(Vector (f a))
type Index (Point f a) 
type Index (Point f a) = Index (f a)
type IxValue (Point f a) 
type IxValue (Point f a) = IxValue (f a)
type Unwrapped (Point f a) 
type Unwrapped (Point f a) = f a
type N (Point v n) Source # 
type N (Point v n) = n
type V (Point v n) Source # 
type V (Point v n) = v

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

Vector spaces have origins.

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

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

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

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

_Point :: (Profunctor p, Functor f) => p (f a) (f (f a)) -> p (Point f a) (f (Point f a)) #

reflectThrough :: (Additive v, Num n) => Point v n -> Point v n -> Point v n Source #

Mirror a point through a given point.

mirror :: (Additive v, Num n) => Point v n -> Point v n Source #

Reflect a point across the origin.

relative2 :: (Additive v, Num n) => Point v n -> (v n -> v n -> v n) -> Point v n -> Point v n -> Point v n Source #

Apply a transformation relative to the given point.

relative3 :: (Additive v, Num n) => Point v n -> (v n -> v n -> v n -> v n) -> Point v n -> Point v n -> Point v n -> Point v n Source #

Apply a transformation relative to the given point.