Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type HasIndexedBasis v = (HasBasis v, TraversableWithIndex (E v) v)
- type Euclidean (v :: Type -> Type) = (HasLinearMap v, HasIndexedBasis v, Metric v)
- class (Euclidean v, Typeable v) => VectorLike v n a | a -> v n where
- vectorLike :: Iso' (v n) a
- unvectorLike :: Iso' a (v n)
- type V2Like = VectorLike V2
- type V3Like = VectorLike V3
- class (Euclidean v, Typeable v) => PointLike v n a | a -> v n where
- type P2Like = PointLike V2
- type P3Like = PointLike V3
Type constraints
type HasIndexedBasis v = (HasBasis v, TraversableWithIndex (E v) v) Source #
type Euclidean (v :: Type -> Type) = (HasLinearMap v, HasIndexedBasis v, Metric v) Source #
Vector like
class (Euclidean v, Typeable v) => VectorLike v n a | a -> v n where Source #
Provides an Iso'
between a
and v n
. This is normally used to
convert between the data type you're already using, a
, and diagram's
native form, v n
.
vectorLike :: Iso' (v n) a Source #
Isomorphism from Point v n
to something PointLike
a
.
>>>
V2 3 5 ^. vectorLike :: (Int, Int)
(3,5)
unvectorLike :: Iso' a (v n) Source #
Isomorphism from something PointLike
a
to Point v n
.
>>>
((3, 5) :: (Int, Int)) ^. unvectorLike
V2 3 5
Instances
VectorLike V2 n (Complex n) Source # | |
Defined in Diagrams.Coordinates.Isomorphic | |
VectorLike V2 n (V2 n) Source # | |
Defined in Diagrams.Coordinates.Isomorphic | |
VectorLike V3 n (V3 n) Source # | |
Defined in Diagrams.Coordinates.Isomorphic | |
n ~ m => VectorLike V2 n (n, m) Source # | |
Defined in Diagrams.Coordinates.Isomorphic vectorLike :: Iso' (V2 n) (n, m) Source # unvectorLike :: Iso' (n, m) (V2 n) Source # | |
(n ~ m, m ~ o) => VectorLike V3 n (n, m, o) Source # | |
Defined in Diagrams.Coordinates.Isomorphic vectorLike :: Iso' (V3 n) (n, m, o) Source # unvectorLike :: Iso' (n, m, o) (V3 n) Source # |
type V2Like = VectorLike V2 Source #
type V3Like = VectorLike V3 Source #
Point like
class (Euclidean v, Typeable v) => PointLike v n a | a -> v n where Source #
Provides an Iso'
between a
and
. This is normally used to
convert between the data type you're already using, Point
v na
, and diagram's
native form,
.Point
v n
pointLike :: Iso' (Point v n) a Source #
unpointLike :: Iso' a (Point v n) Source #
Isomorphism from something PointLike
a
to Point v n
.
>>>
((3, 5) :: (Int, Int)) ^. unpointLike
P (V2 3 5)