Copyright | (c) 2011 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
Basic types for three-dimensional Euclidean space.
- data R3
- 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 Angle
- rad :: Iso' Angle Double
- turn :: Iso' Angle Double
- deg :: Iso' Angle Double
- (@@) :: b -> Iso' a b -> a
- fullTurn :: Angle
- angleRatio :: Angle -> Angle -> Double
- class Direction d where
- toSpherical :: d -> Spherical
- fromSpherical :: Spherical -> d
- data Spherical = Spherical Angle Angle
- asSpherical :: Spherical -> Spherical
3D Euclidean space
The three-dimensional Euclidean vector space R^3.
Eq R3 | |
Ord R3 | |
Read R3 | |
Show R3 | |
Transformable R3 | |
Wrapped R3 | Lens wrapped isomorphisms for R3. |
HasCross3 R3 | |
HasBasis R3 | |
VectorSpace R3 | |
InnerSpace R3 | |
AdditiveGroup R3 | |
HasZ P3 | |
HasZ R3 | |
HasY P3 | |
HasY R3 | |
HasX P3 | |
HasX R3 | |
Coordinates R3 | |
Rewrapped R3 R3 | |
type V R3 = R3 | |
type Unwrapped R3 = (Double, Double, Double) | |
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.
Two-dimensional angles
These are defined in Diagrams.TwoD.Types but reëxported here for convenience.
Angles can be expressed in a variety of units. Internally, they are represented in radians.
rad :: Iso' Angle Double Source
The radian measure of an Angle
a
can be accessed as a
^. rad
. A new Angle
can be defined in radians as pi @@ rad
.
turn :: Iso' Angle Double Source
The measure of an Angle
a
in full circles can be accessed as
a ^. turn
. A new Angle
of one-half circle can be defined in as
1/2 @@ turn
.
deg :: Iso' Angle Double Source
The degree measure of an Angle
a
can be accessed as a
^. deg
. A new Angle
can be defined in degrees as 180 @@
deg
.
(@@) :: b -> Iso' a b -> a infixl 5 Source
30 @@ deg
is an Angle
of the given measure and units.
More generally, @@
reverses the Iso'
on its right, and
applies the Iso'
to the value on the left. Angle
s are the
motivating example where this order improves readability.
angleRatio :: Angle -> Angle -> Double Source
Calculate ratio between two angles.
Directions in 3D
class Direction d where Source
Direction is a type class representing directions in R3. The interface is based on that of the Angle class in 2D.
toSpherical :: d -> Spherical Source
Convert to spherical coördinates
fromSpherical :: Spherical -> d Source
Convert from spherical coördinates
A direction expressed as a pair of spherical coordinates.
`Spherical 0 0` is the direction of unitX
. The first coordinate
represents rotation about the Z axis, the second rotation towards the Z axis.
asSpherical :: Spherical -> Spherical Source
The identity function with a restricted type, for conveniently
restricting unwanted polymorphism. For example, fromDirection
. asSpherical . camForward
gives a unit vector pointing in the
direction of the camera view. Without asSpherical
, the
intermediate type would be ambiguous.