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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.TwoD.Types

Contents

Description

Basic types for two-dimensional Euclidean space.

Synopsis

2D Euclidean space

data R2 Source

The two-dimensional Euclidean vector space R^2. This type is intentionally abstract.

 r2 (3,4) :: R2
 3 ^& 4    :: R2

Note that Diagrams.Coordinates is not re-exported by Diagrams.Prelude and must be explicitly imported.

  • To construct the vector from the origin to a point p, use p .-. origin.
  • To convert a vector v into the point obtained by following v from the origin, use origin .+^ v.
  • To convert a vector back into a pair of components, use unv2 or coords (from Diagrams.Coordinates). These are typically used in conjunction with the ViewPatterns extension:
 foo (unr2 -> (x,y)) = ...
 foo (coords -> x :& y) = ...

Constructors

R2 !Double !Double 

r2 :: (Double, Double) -> R2Source

Construct a 2D vector from a pair of components. See also &.

unr2 :: R2 -> (Double, Double)Source

Convert a 2D vector back into a pair of components. See also coords.

mkR2 :: Double -> Double -> R2Source

Curried form of r2.

type P2 = Point R2Source

Points in R^2. This type is intentionally abstract.

 p2 (3,4)  :: P2
 3 ^& 4    :: P2
  • To construct a point from a vector v, use origin .+^ v.
  • To convert a point p into the vector from the origin to p, use p .-. origin.
  • To convert a point back into a pair of coordinates, use unp2, or coords (from Diagrams.Coordinates). It's common to use these in conjunction with the ViewPatterns extension:
 foo (unp2 -> (x,y)) = ...
 foo (coords -> x :& y) = ...

p2 :: (Double, Double) -> P2Source

Construct a 2D point from a pair of coordinates. See also ^&.

mkP2 :: Double -> Double -> P2Source

Curried form of p2.

unp2 :: P2 -> (Double, Double)Source

Convert a 2D point back into a pair of coordinates. See also coords.

type T2 = Transformation R2Source

Transformations in R^2.

Angles

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.

fullCircle :: Angle a => aSource

Deprecated synonym for fullTurn, retained for backwards compatibility.

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

Convert between two angle representations.

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

Calculate ratio between two angles