Copyright | (c) 2011 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Diagrams.Points
Contents
Description
Points in space. For more tools for working with points and vectors, see Linear.Affine.
Synopsis
- newtype Point (f :: Type -> Type) a = P (f a)
- origin :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a
- (*.) :: forall (v :: Type -> Type) n. (Functor v, Num n) => n -> Point v n -> Point v n
- centroid :: (Additive v, Fractional n) => [Point v n] -> Point v n
- pointDiagram :: forall (v :: Type -> Type) n b m. (Metric v, Fractional n) => Point v n -> QDiagram b v n m
- _Point :: forall (f :: Type -> Type) a. Iso' (Point f a) (f a)
- lensP :: forall (g :: Type -> Type) a. Lens' (Point g a) (g a)
Points
newtype Point (f :: Type -> Type) a Source #
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) | |
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 () | |
Unbox (f a) => MVector MVector (Point f a) | |
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)) | |
Representable f => Representable (Point f) | |
Foldable f => Foldable (Point f) | |
Defined in Linear.Affine Methods fold :: Monoid m => Point f m -> m Source # foldMap :: Monoid m => (a -> m) -> Point f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Point f a -> m Source # foldr :: (a -> b -> b) -> b -> Point f a -> b Source # foldr' :: (a -> b -> b) -> b -> Point f a -> b Source # foldl :: (b -> a -> b) -> b -> Point f a -> b Source # foldl' :: (b -> a -> b) -> b -> Point f a -> b Source # foldr1 :: (a -> a -> a) -> Point f a -> a Source # foldl1 :: (a -> a -> a) -> Point f a -> a Source # toList :: Point f a -> [a] Source # null :: Point f a -> Bool Source # length :: Point f a -> Int Source # elem :: Eq a => a -> Point f a -> Bool Source # maximum :: Ord a => Point f a -> a Source # minimum :: Ord a => Point f a -> a Source # | |
Eq1 f => Eq1 (Point f) | |
Ord1 f => Ord1 (Point f) | |
Defined in Linear.Affine | |
Read1 f => Read1 (Point f) | |
Defined in Linear.Affine Methods liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Point f a) Source # liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Point f a] Source # liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Point f a) Source # liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Point f a] Source # | |
Show1 f => Show1 (Point f) | |
Traversable f => Traversable (Point f) | |
Defined in Linear.Affine | |
Applicative f => Applicative (Point f) | |
Functor f => Functor (Point f) | |
Monad f => Monad (Point f) | |
Serial1 f => Serial1 (Point f) | |
Defined in Linear.Affine Methods serializeWith :: MonadPut m => (a -> m ()) -> Point f a -> m () deserializeWith :: MonadGet m => m a -> m (Point f a) | |
HasPhi v => HasPhi (Point v) Source # | |
HasTheta v => HasTheta (Point v) 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 |
HasR v => HasR (Point v) Source # | |
Distributive f => Distributive (Point f) | |
Defined in Linear.Affine | |
Hashable1 f => Hashable1 (Point f) | |
Defined in Linear.Affine | |
Additive f => Affine (Point f) | |
Defined in Linear.Affine | |
Metric f => Metric (Point f) | |
Finite f => Finite (Point f) | |
R1 f => R1 (Point f) | |
R2 f => R2 (Point f) | |
R3 f => R3 (Point f) | |
R4 f => R4 (Point f) | |
Additive f => Additive (Point f) | |
Defined in Linear.Affine Methods zero :: Num a => Point f a Source # (^+^) :: Num a => Point f a -> Point f a -> Point f a Source # (^-^) :: Num a => Point f a -> Point f a -> Point f a Source # lerp :: Num a => a -> Point f a -> Point f a -> Point f a Source # liftU2 :: (a -> a -> a) -> Point f a -> Point f a -> Point f a Source # liftI2 :: (a -> b -> c) -> Point f a -> Point f b -> Point f c Source # | |
Apply f => Apply (Point f) | |
Bind f => Bind (Point f) | |
Generic1 (Point f :: Type -> Type) | |
Functor v => Cosieve (Query v) (Point v) | |
(Typeable f, Typeable a, Data (f a)) => Data (Point f a) | |
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) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Point f a) Source # toConstr :: Point f a -> Constr Source # dataTypeOf :: Point f a -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Point f a)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Point f a)) Source # gmapT :: (forall b. Data b => b -> b) -> Point f a -> Point f a Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Point f a -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Point f a -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Point f a -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Point f a -> m (Point f a) Source # | |
Storable (f a) => Storable (Point f a) | |
Defined in Linear.Affine Methods sizeOf :: Point f a -> Int Source # alignment :: Point f a -> Int Source # peekElemOff :: Ptr (Point f a) -> Int -> IO (Point f a) Source # pokeElemOff :: Ptr (Point f a) -> Int -> Point f a -> IO () Source # peekByteOff :: Ptr b -> Int -> IO (Point f a) Source # pokeByteOff :: Ptr b -> Int -> Point f a -> IO () Source # | |
Monoid (f a) => Monoid (Point f a) | |
Semigroup (f a) => Semigroup (Point f a) | |
Generic (Point f a) | |
Ix (f a) => Ix (Point f a) | |
Defined in Linear.Affine Methods range :: (Point f a, Point f a) -> [Point f a] Source # index :: (Point f a, Point f a) -> Point f a -> Int Source # unsafeIndex :: (Point f a, Point f a) -> Point f a -> Int Source # inRange :: (Point f a, Point f a) -> Point f a -> Bool Source # | |
Num (f a) => Num (Point f a) | |
Defined in Linear.Affine Methods (+) :: Point f a -> Point f a -> Point f a Source # (-) :: Point f a -> Point f a -> Point f a Source # (*) :: Point f a -> Point f a -> Point f a Source # negate :: Point f a -> Point f a Source # abs :: Point f a -> Point f a Source # signum :: Point f a -> Point f a Source # fromInteger :: Integer -> Point f a Source # | |
Read (f a) => Read (Point f a) | |
Fractional (f a) => Fractional (Point f a) | |
Show (f a) => Show (Point f a) | |
Binary (f a) => Binary (Point f a) | |
Serial (f a) => Serial (Point f a) | |
Defined in Linear.Affine | |
Serialize (f a) => Serialize (Point f a) | |
NFData (f a) => NFData (Point f a) | |
Defined in Linear.Affine | |
(OrderedField n, Metric v) => Enveloped (Point v n) | |
Defined in Diagrams.Core.Envelope | |
(Additive v, Num n) => HasOrigin (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). |
(Additive v, Num n) => Transformable (Point v n) | |
Coordinates (v n) => Coordinates (Point v n) Source # | |
Defined in Diagrams.Coordinates | |
Eq (f a) => Eq (Point f a) | |
Ord (f a) => Ord (Point f a) | |
Defined in Linear.Affine | |
Hashable (f a) => Hashable (Point f a) | |
Ixed (f a) => Ixed (Point f a) | |
Defined in Linear.Affine | |
Wrapped (Point f a) | |
Epsilon (f a) => Epsilon (Point f a) | |
Random (f a) => Random (Point f a) | |
Unbox (f a) => Unbox (Point f a) | |
Defined in Linear.Affine | |
r ~ Point u n => Deformable (Point v n) r Source # | |
(Additive v, Num n, r ~ Point u n) => AffineMappable (Point v n) r Source # | |
t ~ Point g b => Rewrapped (Point f a) t | |
Defined in Linear.Affine | |
LinearMappable (Point v n) (Point u m) Source # | |
Traversable f => Each (Point f a) (Point f b) a b | |
(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. |
Defined in Diagrams.BoundingBox Methods each :: Traversal (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') Source # | |
Each (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') Source # | |
Defined in Diagrams.Segment Methods each :: Traversal (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') Source # | |
newtype MVector s (Point f a) | |
Defined in Linear.Affine | |
type Rep (Point f) | |
Defined in Linear.Affine | |
type Diff (Point f) | |
Defined in Linear.Affine | |
type Size (Point f) | |
Defined in Linear.Affine | |
type Rep1 (Point f :: Type -> Type) | |
type Rep (Point f a) | |
Defined in Linear.Affine | |
type N (Point v n) | |
Defined in Diagrams.Core.Points | |
type V (Point v n) | |
Defined in Diagrams.Core.Points | |
type Decomposition (Point v n) Source # | |
Defined in Diagrams.Coordinates | |
type FinalCoord (Point v n) Source # | |
Defined in Diagrams.Coordinates | |
type PrevDim (Point v n) Source # | |
Defined in Diagrams.Coordinates | |
type Index (Point f a) | |
Defined in Linear.Affine | |
type IxValue (Point f a) | |
Defined in Linear.Affine | |
type Unwrapped (Point f a) | |
Defined in Linear.Affine | |
newtype Vector (Point f a) | |
Defined in Linear.Affine |
origin :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a Source #
Vector spaces have origins.
(*.) :: forall (v :: Type -> Type) n. (Functor v, Num n) => n -> Point v n -> Point v n Source #
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 :: forall (v :: Type -> Type) n b m. (Metric v, Fractional n) => Point v n -> QDiagram b v n m Source #
Create a "point diagram", which has no content, no trace, an empty query, and a point envelope.