| 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.
- data R3 = R3 !Double !Double !Double
- r3 :: (Double, Double, Double) -> R3
- unr3 :: R3 -> (Double, Double, Double)
- mkR3 :: Double -> Double -> Double -> R3
- type P3 = Point R3
- p3 :: (Double, Double, Double) -> P3
- unp3 :: P3 -> (Double, Double, Double)
- mkP3 :: Double -> Double -> Double -> P3
- type T3 = Transformation R3
- r3Iso :: Iso' R3 (Double, Double, Double)
- p3Iso :: Iso' P3 (Double, Double, Double)
- data Direction
- direction :: R3 -> Direction
- fromDirection :: Direction -> R3
- angleBetweenDirs :: Direction -> Direction -> Angle
- class Spherical t where
- class Cylindrical t where- cylindrical :: Iso' t (Double, Angle, Double)
 
- class HasPhi t where
3D Euclidean space
The three-dimensional Euclidean vector space R^3.
Instances
| Eq R3 | |
| Ord R3 | |
| Read R3 | |
| Show R3 | |
| Transformable R3 | |
| HasCross3 R3 | |
| HasBasis R3 | |
| VectorSpace R3 | |
| InnerSpace R3 | |
| AdditiveGroup R3 | |
| HasR P3 | |
| HasR R3 | |
| HasZ P3 | |
| HasZ R3 | |
| HasY P3 | |
| HasY R3 | |
| HasX P3 | |
| HasX R3 | |
| Coordinates R3 | |
| HasTheta P3 | |
| HasTheta R3 | |
| HasPhi P3 | |
| HasPhi R3 | |
| Cylindrical P3 | |
| Cylindrical R3 | |
| Spherical P3 | |
| Spherical R3 | |
| type V R3 = R3 | |
| type Basis R3 = Either () (Either () ()) | |
| type Scalar R3 = Double | |
| type FinalCoord R3 = Double | |
| type PrevDim R3 = R2 | |
| type Decomposition R3 = (:&) ((:&) Double Double) Double | 
type T3 = Transformation R3 Source
Transformations in R^3.
Directions in 3D
A Direction represents directions in R3.  The constructor is
 not exported; Directions can be used with fromDirection and the
 lenses provided by its instances.
direction :: R3 -> Direction Source
direction v is the direction in which v points.  Returns an
   unspecified value when given the zero vector as input.
fromDirection :: Direction -> R3 Source
fromDirection d is the unit vector in the direction d.
angleBetweenDirs :: Direction -> Direction -> Angle Source
compute the positive angle between the two directions in their common plane
other coördinate systems
class Spherical t where Source
Types which can be expressed in spherical 3D coordinates, as a triple (r,θ,φ), where θ is rotation about the Z axis, and φ is the angle from the Z axis.
class Cylindrical t where Source
Types which can be expressed in cylindrical 3D coordinates.
Instances