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

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

Diagrams.Direction

Description

Type for representing directions, polymorphic in vector space

Synopsis

Documentation

data Direction v n Source

A vector is described by a Direction and a magnitude. So we can think of a Direction as a vector that has forgotten its magnitude. Directions can be used with fromDirection and the lenses provided by its instances.

Instances

Functor v => Functor (Direction v) Source 
HasPhi v => HasPhi (Direction v) Source 
HasTheta v => HasTheta (Direction v) Source 
Eq (v n) => Eq (Direction v n) Source 
Ord (v n) => Ord (Direction v n) Source 
Read (v n) => Read (Direction v n) Source 
Show (v n) => Show (Direction v n) Source 
((~) (* -> *) (V (v n)) v, (~) * (N (v n)) n, Transformable (v n)) => Transformable (Direction v n) Source 
type V (Direction v n) = v Source 
type N (Direction v n) = n Source 

_Dir :: Iso' (Direction v n) (v n) Source

_Dir is provided to allow efficient implementations of functions in particular vector-spaces, but should be used with care as it exposes too much information.

direction :: v n -> Direction v n Source

direction v is the direction in which v points. Returns an unspecified value when given the zero vector as input.

dir :: v n -> Direction v n Source

Synonym for direction.

fromDirection :: (Metric v, Floating n) => Direction v n -> v n Source

fromDirection d is the unit vector in the direction d.

fromDir :: (Metric v, Floating n) => Direction v n -> v n Source

Synonym for fromDirection.

angleBetweenDirs :: (Metric v, Floating n) => Direction v n -> Direction v n -> Angle n Source

compute the positive angle between the two directions in their common plane

dirBetween :: (Additive v, Num n) => Point v n -> Point v n -> Direction v n Source

dirBetween p q returns the directions from p to q