diagrams-lib-1.3: Embedded domain-specific language for declarative graphics

Copyright(c) 2011 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.ThreeD.Types

Contents

Description

Basic types for three-dimensional Euclidean space.

Synopsis

3D Euclidean space

r3 :: (n, n, n) -> V3 n Source

Construct a 3D vector from a triple of components.

unr3 :: V3 n -> (n, n, n) Source

Convert a 3D vector back into a triple of components.

mkR3 :: n -> n -> n -> V3 n Source

Curried version of r3.

p3 :: (n, n, n) -> P3 n Source

Construct a 3D point from a triple of coordinates.

unp3 :: P3 n -> (n, n, n) Source

Convert a 3D point back into a triple of coordinates.

mkP3 :: n -> n -> n -> P3 n Source

Curried version of r3.

r3Iso :: Iso' (V3 n) (n, n, n) Source

p3Iso :: Iso' (P3 n) (n, n, n) Source

project :: (Metric v, Fractional a) => v a -> v a -> v a

project u v computes the projection of v onto u.

data V3 a :: * -> *

A 3-dimensional vector

Constructors

V3 !a !a !a 

Instances

Monad V3 
Functor V3 
MonadFix V3 
Applicative V3 
Foldable V3 
Traversable V3 
Generic1 V3 
Apply V3 
Distributive V3 
Representable V3 
MonadZip V3 
Serial1 V3 
Additive V3 
Traversable1 V3 
Affine V3 
R3 V3 
R2 V3 
R1 V3 
Metric V3 
Foldable1 V3 
Bind V3 
Eq1 V3 
Ord1 V3 
Read1 V3 
Show1 V3 
Unbox a => Vector Vector (V3 a) 
Unbox a => MVector MVector (V3 a) 
Bounded a => Bounded (V3 a) 
Eq a => Eq (V3 a) 
Floating a => Floating (V3 a) 
Fractional a => Fractional (V3 a) 
Data a => Data (V3 a) 
Num a => Num (V3 a) 
Ord a => Ord (V3 a) 
Read a => Read (V3 a) 
Show a => Show (V3 a) 
Ix a => Ix (V3 a) 
Generic (V3 a) 
Storable a => Storable (V3 a) 
Binary a => Binary (V3 a) 
Serial a => Serial (V3 a) 
Serialize a => Serialize (V3 a) 
NFData a => NFData (V3 a) 
Hashable a => Hashable (V3 a) 
Unbox a => Unbox (V3 a) 
Ixed (V3 a) 
Epsilon a => Epsilon (V3 a) 
Coordinates (V3 n) 
FunctorWithIndex (E V3) V3 
FoldableWithIndex (E V3) V3 
TraversableWithIndex (E V3) V3 
Each (V3 a) (V3 b) a b 
TypeableFloat n => Traced (BoundingBox V3 n) 
type Rep1 V3 = D1 D1V3 (C1 C1_0V3 ((:*:) (S1 NoSelector Par1) ((:*:) (S1 NoSelector Par1) (S1 NoSelector Par1)))) 
type Rep V3 = E V3 
type Diff V3 = V3 
data MVector s (V3 a) = MV_V3 !Int (MVector s a) 
type Rep (V3 a) = D1 D1V3 (C1 C1_0V3 ((:*:) (S1 NoSelector (Rec0 a)) ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 a))))) 
type V (V3 n) = V3 
type N (V3 n) = n 
data Vector (V3 a) = V_V3 !Int (Vector a) 
type Index (V3 a) = E V3 
type IxValue (V3 a) = a 
type FinalCoord (V3 n) = n 
type PrevDim (V3 n) = V2 n 
type Decomposition (V3 n) = (:&) ((:&) n n) n 

type P3 = Point V3 Source

class R1 t where

A space that has at least 1 basis vector _x.

Minimal complete definition

Nothing

Methods

_x :: Functor f => (a -> f a) -> t a -> f (t a)

>>> V1 2 ^._x
2
>>> V1 2 & _x .~ 3
V1 3

Instances

R1 Identity 
R1 V4 
R1 V3 
R1 V2 
R1 V1 
R1 f => R1 (Point f) 

class R1 t => R2 t where

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

Nothing

Methods

_y :: Functor f => (a -> f a) -> t a -> f (t a)

>>> V2 1 2 ^._y
2
>>> V2 1 2 & _y .~ 3
V2 1 3

_xy :: Functor f => (V2 a -> f (V2 a)) -> t a -> f (t a)

Instances

R2 V4 
R2 V3 
R2 V2 
R2 f => R2 (Point f) 

class R2 t => R3 t where

A space that distinguishes 3 orthogonal basis vectors: _x, _y, and _z. (It may have more)

Minimal complete definition

Nothing

Methods

_z :: Functor f => (a -> f a) -> t a -> f (t a)

>>> V3 1 2 3 ^. _z
3

_xyz :: Functor f => (V3 a -> f (V3 a)) -> t a -> f (t a)

Instances

R3 V4 
R3 V3 
R3 f => R3 (Point f)