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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.ThreeD.Types

Contents

Description

Basic types for three-dimensional Euclidean space.

Synopsis

3D Euclidean space

data R3 Source

The three-dimensional Euclidean vector space R^3.

r3 :: (Double, Double, Double) -> R3Source

Construct a 3D vector from a triple of components.

unr3 :: R3 -> (Double, Double, Double)Source

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

mkR3 :: Double -> Double -> Double -> R3Source

Curried version of r3.

type P3 = Point R3Source

Points in R^3.

p3 :: (Double, Double, Double) -> P3Source

Construct a 3D point from a triple of coordinates.

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

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

mkP3 :: Double -> Double -> Double -> P3Source

Curried version of r3.

type T3 = Transformation R3Source

Transformations in R^3.

Two-dimensional angles

These are defined in Diagrams.TwoD.Types but reëxported here for convenience.

class Num a => Angle a whereSource

Type class for types that measure angles.

Methods

toTurn :: a -> TurnSource

Convert to a turn, i.e. a fraction of a circle.

fromTurn :: Turn -> aSource

Convert from a turn, i.e. a fraction of a circle.

Instances

Angle Turn 
Angle Rad

tau radians = 1 full turn.

Angle Deg

360 degrees = 1 full turn.

newtype Turn Source

Newtype wrapper used to represent angles as fractions of a circle. For example, 1/3 turn = tau/3 radians = 120 degrees.

Constructors

Turn Double 

asTurn :: Turn -> TurnSource

The identity function with a restricted type, for conveniently declaring that some value should have type Turn. For example, rotation . asTurn . fromRational constructs a rotation from a rational value considered as a Turn. Without asTurn, the angle type would be ambiguous.

type CircleFrac = TurnSource

Deprecated synonym for Turn, retained for backwards compatibility.

newtype Rad Source

Newtype wrapper for representing angles in radians.

Constructors

Rad Double 

asRad :: Rad -> RadSource

The identity function with a restricted type, for conveniently declaring that some value should have type Rad. For example, rotation . asRad . fromRational constructs a rotation from a rational value considered as a value in radians. Without asRad, the angle type would be ambiguous.

newtype Deg Source

Newtype wrapper for representing angles in degrees.

Constructors

Deg Double 

asDeg :: Deg -> DegSource

The identity function with a restricted type, for conveniently declaring that some value should have type Deg. For example, rotation . asDeg . fromIntegral constructs a rotation from an integral value considered as a value in degrees. Without asDeg, the angle type would be ambiguous.

fullTurn :: Angle a => aSource

An angle representing one full turn.

convertAngle :: (Angle a, Angle b) => a -> bSource

Convert between two angle representations.

angleRatio :: Angle a => a -> a -> DoubleSource

Calculate ratio between two angles

Directions in 3D

class Direction d whereSource

Direction is a type class representing directions in R3. The interface is based on that of the Angle class in 2D.

Methods

toSpherical :: Angle a => d -> Spherical aSource

Convert to polar angles

fromSpherical :: Angle a => Spherical a -> dSource

Convert from polar angles

Instances

data Spherical a Source

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.

Constructors

Spherical a a 

asSpherical :: Spherical Turn -> Spherical TurnSource

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.