Copyright | (c) 2011 diagrams-core team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
A type for points (as distinct from vectors).
- newtype Point f a :: (* -> *) -> * -> * = P (f a)
- origin :: (Additive f, Num a) => Point f a
- (*.) :: (Functor v, Num n) => n -> Point v n -> Point v n
- relative :: (Additive f, Num a) => Point f a -> Iso' (Point f a) (f a)
- _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
- mirror :: (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 a :: (* -> *) -> * -> *
A handy wrapper to help distinguish points from vectors at the type level
P (f a) |
Unbox (f a) => Vector Vector (Point f a) | |
Unbox (f a) => MVector MVector (Point f a) | |
Monad f => Monad (Point f) | |
Functor f => Functor (Point f) | |
Applicative f => Applicative (Point f) | |
Foldable f => Foldable (Point f) | |
Traversable f => Traversable (Point f) | |
Generic1 (Point f) | |
Distributive f => Distributive (Point f) | |
Representable f => Representable (Point f) | |
Serial1 f => Serial1 (Point f) | |
Additive f => Affine (Point f) | |
R4 f => R4 (Point f) | |
R3 f => R3 (Point f) | |
R2 f => R2 (Point f) | |
R1 f => R1 (Point f) | |
Metric f => Metric (Point f) | |
Additive f => Additive (Point f) | |
Apply f => Apply (Point f) | |
Bind f => Bind (Point f) | |
Eq1 f => Eq1 (Point f) | |
Ord1 f => Ord1 (Point f) | |
Read1 f => Read1 (Point f) | |
Show1 f => Show1 (Point f) | |
Eq (f a) => Eq (Point f a) | |
Fractional (f a) => Fractional (Point f a) | |
(Data (f a), Typeable (* -> *) f, Typeable * a) => Data (Point f a) | |
Num (f a) => Num (Point f a) | |
Ord (f a) => Ord (Point f a) | |
Read (f a) => Read (Point f a) | |
Show (f a) => Show (Point f a) | |
Ix (f a) => Ix (Point f a) | |
Generic (Point f a) | |
Storable (f a) => Storable (Point f a) | |
Binary (f a) => Binary (Point f a) | |
Serial (f a) => Serial (Point f a) | |
Serialize (f a) => Serialize (Point f a) | |
NFData (f a) => NFData (Point f a) | |
Hashable (f a) => Hashable (Point f a) | |
Unbox (f a) => Unbox (Point f a) | |
Ixed (f a) => Ixed (Point f a) | |
Wrapped (Point f a) | |
Epsilon (f a) => Epsilon (Point f a) | |
(Additive v, Num n) => HasOrigin (Point v n) Source | |
(Additive v, Num n) => Transformable (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). |
(OrderedField n, Metric v) => Enveloped (Point v n) Source | |
(~) * t (Point g b) => Rewrapped (Point f a) t | |
Traversable f => Each (Point f a) (Point f b) a b | |
data MVector s (Point f a) = MV_P !(MVector s (f a)) | |
type Rep1 (Point f) = D1 D1Point (C1 C1_0Point (S1 NoSelector (Rec1 f))) | |
type Rep (Point f) = Rep f | |
type Diff (Point f) = f | |
type Rep (Point f a) = D1 D1Point (C1 C1_0Point (S1 NoSelector (Rec0 (f a)))) | |
data Vector (Point f a) = V_P !(Vector (f a)) | |
type Index (Point f a) = Index (f a) | |
type IxValue (Point f a) = IxValue (f a) | |
type Unwrapped (Point f a) = f a | |
type N (Point v n) = n Source | |
type V (Point v n) = v Source |
(*.) :: (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.