| Copyright | (c) 2011 diagrams-lib team (see LICENSE) | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | diagrams-discuss@googlegroups.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Diagrams.ThreeD.Types
Description
Basic types for three-dimensional Euclidean space.
Synopsis
- r3 :: (n, n, n) -> V3 n
- unr3 :: V3 n -> (n, n, n)
- mkR3 :: n -> n -> n -> V3 n
- p3 :: (n, n, n) -> P3 n
- unp3 :: P3 n -> (n, n, n)
- mkP3 :: n -> n -> n -> P3 n
- r3Iso :: Iso' (V3 n) (n, n, n)
- p3Iso :: Iso' (P3 n) (n, n, n)
- project :: (Metric v, Fractional a) => v a -> v a -> v a
- r3SphericalIso :: RealFloat n => Iso' (V3 n) (n, Angle n, Angle n)
- r3CylindricalIso :: RealFloat n => Iso' (V3 n) (n, Angle n, n)
- data V3 a = V3 !a !a !a
- type P3 = Point V3
- type T3 = Transformation V3
- class R1 (t :: Type -> Type) where
- class R1 t => R2 (t :: Type -> Type) where
- class R2 t => R3 (t :: Type -> Type) where
3D Euclidean space
project :: (Metric v, Fractional a) => v a -> v a -> v a #
project u v computes the projection of v onto u.
A 3-dimensional vector
Constructors
| V3 !a !a !a | 
Instances
type T3 = Transformation V3 Source #
class R1 (t :: Type -> Type) where #
A space that has at least 1 basis vector _x.
class R1 t => R2 (t :: Type -> Type) where #
Minimal complete definition
Methods
>>>V2 1 2 ^._y2
>>>V2 1 2 & _y .~ 3V2 1 3
class R2 t => R3 (t :: Type -> Type) where #
Instances
| R3 Quaternion | |
| Defined in Linear.Quaternion | |
| R3 V4 | |
| R3 V3 | |
| R3 f => R3 (Point f) | |