Copyright | (c) 2011 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | [email protected] |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Diagrams.Core.Points
Contents
Description
A type for points (as distinct from vectors).
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
- relative :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a)
- _Point :: forall f1 a g b p f2. (Profunctor p, Functor f2) => p (f1 a) (f2 (g b)) -> p (Point f1 a) (f2 (Point g b))
- reflectThrough :: forall (v :: Type -> Type) n. (Additive v, Num n) => Point v n -> Point v n -> Point v n
- mirror :: forall (v :: Type -> Type) n. (Additive v, Num n) => Point v n -> Point v n
- relative2 :: (Additive v, Num n) => Point v n -> (v n -> v n -> v n) -> Point v n -> Point v n -> Point v n
- 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
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
Generic1 (Point f :: Type -> Type) | |||||
Defined in Linear.Affine | |||||
Unbox (f a) => Vector Vector (Point f a) | |||||
Defined in Linear.Affine Methods basicUnsafeFreeze :: Mutable Vector s (Point f a) -> ST s (Vector (Point f a)) basicUnsafeThaw :: Vector (Point f a) -> ST s (Mutable Vector s (Point f a)) basicLength :: Vector (Point f a) -> Int basicUnsafeSlice :: Int -> Int -> Vector (Point f a) -> Vector (Point f a) basicUnsafeIndexM :: Vector (Point f a) -> Int -> Box (Point f a) basicUnsafeCopy :: Mutable Vector s (Point f a) -> Vector (Point f a) -> ST s () | |||||
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 :: Int -> ST s (MVector s (Point f a)) basicInitialize :: MVector s (Point f a) -> ST s () basicUnsafeReplicate :: Int -> Point f a -> ST s (MVector s (Point f a)) basicUnsafeRead :: MVector s (Point f a) -> Int -> ST s (Point f a) basicUnsafeWrite :: MVector s (Point f a) -> Int -> Point f a -> ST s () basicClear :: MVector s (Point f a) -> ST s () basicSet :: MVector s (Point f a) -> Point f a -> ST s () basicUnsafeCopy :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () basicUnsafeMove :: MVector s (Point f a) -> MVector s (Point f a) -> ST s () basicUnsafeGrow :: MVector s (Point f a) -> Int -> ST s (MVector s (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 # foldMap :: Monoid m => (a -> m) -> Point f a -> 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 # elem :: Eq a => a -> Point f a -> Bool # maximum :: Ord a => Point f a -> a # minimum :: Ord a => Point f a -> a # | |||||
Eq1 f => Eq1 (Point f) | |||||
Ord1 f => Ord1 (Point f) | |||||
Defined in Linear.Affine | |||||
Read1 f => Read1 (Point f) | |||||
Defined in Linear.Affine | |||||
Show1 f => Show1 (Point f) | |||||
Traversable f => Traversable (Point f) | |||||
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) # | |||||
Distributive f => Distributive (Point f) | |||||
Hashable1 f => Hashable1 (Point f) | |||||
Defined in Linear.Affine | |||||
Additive f => Affine (Point f) | |||||
Defined in Linear.Affine Associated Types
| |||||
Metric f => Metric (Point f) | |||||
Defined in Linear.Affine | |||||
Finite f => Finite (Point f) | |||||
R1 f => R1 (Point f) | |||||
Defined in Linear.Affine | |||||
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 (^+^) :: 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) | |||||
Bind f => Bind (Point f) | |||||
Functor v => Cosieve (Query v) (Point v) Source # | |||||
Defined in Diagrams.Core.Query | |||||
(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) # 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 :: forall r r'. (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) # | |||||
Storable (f a) => Storable (Point f a) | |||||
Defined in Linear.Affine | |||||
Monoid (f a) => Monoid (Point f a) | |||||
Semigroup (f a) => Semigroup (Point f a) | |||||
Generic (Point f a) | |||||
Defined in Linear.Affine Associated Types
| |||||
Ix (f a) => Ix (Point f a) | |||||
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 # | |||||
Num (f a) => Num (Point f a) | |||||
Defined in Linear.Affine | |||||
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) Source # | |||||
Defined in Diagrams.Core.Envelope | |||||
(Additive v, Num n) => HasOrigin (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). | ||||
(Additive v, Num n) => Transformable (Point v n) Source # | |||||
Eq (f a) => Eq (Point f a) | |||||
Ord (f a) => Ord (Point f a) | |||||
Hashable (f a) => Hashable (Point f a) | |||||
Defined in Linear.Affine | |||||
Ixed (f a) => Ixed (Point f a) | |||||
Defined in Linear.Affine | |||||
Wrapped (Point f a) | |||||
Epsilon (f a) => Epsilon (Point f a) | |||||
Defined in Linear.Affine | |||||
Random (f a) => Random (Point f a) | |||||
Unbox (f a) => Unbox (Point f a) | |||||
Defined in Linear.Affine | |||||
t ~ Point g b => Rewrapped (Point f a) t | |||||
Defined in Linear.Affine | |||||
Traversable f => Each (Point f a) (Point f b) a b | |||||
type Rep1 (Point f :: Type -> Type) | |||||
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 Rep (Point f a) | |||||
Defined in Linear.Affine | |||||
type N (Point v n) Source # | |||||
Defined in Diagrams.Core.Points | |||||
type V (Point v n) Source # | |||||
Defined in Diagrams.Core.Points | |||||
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 #
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 (*^)
.
relative :: forall (f :: Type -> Type) a. (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a) #
An isomorphism between points and vectors, given a reference point.
_Point :: forall f1 a g b p f2. (Profunctor p, Functor f2) => p (f1 a) (f2 (g b)) -> p (Point f1 a) (f2 (Point g b)) #
reflectThrough :: forall (v :: Type -> Type) n. (Additive v, Num n) => Point v n -> Point v n -> Point v n Source #
Mirror a point through a given point.
mirror :: forall (v :: Type -> Type) n. (Additive v, Num n) => Point v n -> Point v n Source #
Reflect a point across the origin.