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

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

Diagrams.Angle

Contents

Description

Type for representing angles.

Synopsis

Angle type

data Angle n Source #

Angles can be expressed in a variety of units. Internally, they are represented in radians.

Instances

Functor Angle Source # 

Methods

fmap :: (a -> b) -> Angle a -> Angle b #

(<$) :: a -> Angle b -> Angle a #

Applicative Angle Source # 

Methods

pure :: a -> Angle a #

(<*>) :: Angle (a -> b) -> Angle a -> Angle b #

liftA2 :: (a -> b -> c) -> Angle a -> Angle b -> Angle c #

(*>) :: Angle a -> Angle b -> Angle b #

(<*) :: Angle a -> Angle b -> Angle a #

Additive Angle Source # 

Methods

zero :: Num a => Angle a #

(^+^) :: Num a => Angle a -> Angle a -> Angle a #

(^-^) :: Num a => Angle a -> Angle a -> Angle a #

lerp :: Num a => a -> Angle a -> Angle a -> Angle a #

liftU2 :: (a -> a -> a) -> Angle a -> Angle a -> Angle a #

liftI2 :: (a -> b -> c) -> Angle a -> Angle b -> Angle c #

Enum n => Enum (Angle n) Source # 

Methods

succ :: Angle n -> Angle n #

pred :: Angle n -> Angle n #

toEnum :: Int -> Angle n #

fromEnum :: Angle n -> Int #

enumFrom :: Angle n -> [Angle n] #

enumFromThen :: Angle n -> Angle n -> [Angle n] #

enumFromTo :: Angle n -> Angle n -> [Angle n] #

enumFromThenTo :: Angle n -> Angle n -> Angle n -> [Angle n] #

Eq n => Eq (Angle n) Source # 

Methods

(==) :: Angle n -> Angle n -> Bool #

(/=) :: Angle n -> Angle n -> Bool #

Ord n => Ord (Angle n) Source # 

Methods

compare :: Angle n -> Angle n -> Ordering #

(<) :: Angle n -> Angle n -> Bool #

(<=) :: Angle n -> Angle n -> Bool #

(>) :: Angle n -> Angle n -> Bool #

(>=) :: Angle n -> Angle n -> Bool #

max :: Angle n -> Angle n -> Angle n #

min :: Angle n -> Angle n -> Angle n #

Read n => Read (Angle n) Source # 
Show n => Show (Angle n) Source # 

Methods

showsPrec :: Int -> Angle n -> ShowS #

show :: Angle n -> String #

showList :: [Angle n] -> ShowS #

Num n => Semigroup (Angle n) Source # 

Methods

(<>) :: Angle n -> Angle n -> Angle n #

sconcat :: NonEmpty (Angle n) -> Angle n #

stimes :: Integral b => b -> Angle n -> Angle n #

Num n => Monoid (Angle n) Source # 

Methods

mempty :: Angle n #

mappend :: Angle n -> Angle n -> Angle n #

mconcat :: [Angle n] -> Angle n #

((~) (* -> *) (V t) V2, (~) * (N t) n, Transformable t, Floating n) => Action (Angle n) t Source #

Angles act on other things by rotation.

Methods

act :: Angle n -> t -> t #

type N (Angle n) Source # 
type N (Angle n) = n

Using angles

(@@) :: b -> AReview a b -> a infixl 5 Source #

30 @@ deg is an Angle of the given measure and units.

>>> pi @@ rad
3.141592653589793 @@ rad
>>> 1 @@ turn
6.283185307179586 @@ rad
>>> 30 @@ deg
0.5235987755982988 @@ rad

For Iso's, (@@) reverses the Iso' on its right, and applies the Iso' to the value on the left. Angles are the motivating example where this order improves readability.

This is the same as a flipped review.

(@@) :: a -> Iso'      s a -> s
(@@) :: a -> Prism'    s a -> s
(@@) :: a -> Review    s a -> s
(@@) :: a -> Equality' s a -> s

rad :: Iso' (Angle n) n 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 :: Floating n => Iso' (Angle n) n 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 :: Floating n => Iso' (Angle n) n 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.

Common angles

fullTurn :: Floating v => Angle v Source #

An angle representing one full turn.

halfTurn :: Floating v => Angle v Source #

An angle representing a half turn.

quarterTurn :: Floating v => Angle v Source #

An angle representing a quarter turn.

Trigonometric functions

sinA :: Floating n => Angle n -> n Source #

The sine of the given Angle.

cosA :: Floating n => Angle n -> n Source #

The cosine of the given Angle.

tanA :: Floating n => Angle n -> n Source #

The tangent function of the given Angle.

asinA :: Floating n => n -> Angle n Source #

The Angle with the given sine.

acosA :: Floating n => n -> Angle n Source #

The Angle with the given cosine.

atanA :: Floating n => n -> Angle n Source #

The Angle with the given tangent.

atan2A :: RealFloat n => n -> n -> Angle n Source #

atan2A y x is the angle between the positive x-axis and the vector given by the coordinates (x, y). The Angle returned is in the [-pi,pi] range.

atan2A' :: OrderedField n => n -> n -> Angle n Source #

Similar to atan2A but without the RealFloat constraint. This means it doesn't handle negative zero cases. However, for most geometric purposes, the outcome will be the same.

Angle utilities

angleBetween :: (Metric v, Floating n, Ord n) => v n -> v n -> Angle n Source #

Compute the positive angle between the two vectors in their common plane in the [0,pi] range. For a signed angle see signedAngleBetween.

Returns NaN if either of the vectors are zero.

angleRatio :: Floating n => Angle n -> Angle n -> n Source #

Calculate ratio between two angles.

normalizeAngle :: (Floating n, Real n) => Angle n -> Angle n Source #

Normalize an angle so that it lies in the [0,tau) range.

Classes

class HasTheta t where Source #

The class of types with at least one angle coordinate, called _theta.

Minimal complete definition

_theta

Methods

_theta :: RealFloat n => Lens' (t n) (Angle n) Source #

Instances

HasTheta v => HasTheta (Point v) Source # 

Methods

_theta :: RealFloat n => Lens' (Point v n) (Angle n) Source #

HasTheta v => HasTheta (Direction v) Source # 

Methods

_theta :: RealFloat n => Lens' (Direction v n) (Angle n) Source #

class HasTheta t => HasPhi t where Source #

The class of types with at least two angle coordinates, the second called _phi. _phi is the positive angle measured from the z axis.

Minimal complete definition

_phi

Methods

_phi :: RealFloat n => Lens' (t n) (Angle n) Source #

Instances

HasPhi v => HasPhi (Point v) Source # 

Methods

_phi :: RealFloat n => Lens' (Point v n) (Angle n) Source #

HasPhi v => HasPhi (Direction v) Source # 

Methods

_phi :: RealFloat n => Lens' (Direction v n) (Angle n) Source #

Rotation

rotation :: Floating n => Angle n -> Transformation V2 n Source #

Create a transformation which performs a rotation about the local origin by the given angle. See also rotate.

rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t Source #

Rotate about the local origin by the given angle. Positive angles correspond to counterclockwise rotation, negative to clockwise. The angle can be expressed using any of the Isos on Angle. For example, rotate (1/4 @@ turn), rotate (tau/4 @@ rad), and rotate (90 @@ deg) all represent the same transformation, namely, a counterclockwise rotation by a right angle. To rotate about some point other than the local origin, see rotateAbout.

Note that writing rotate (1/4), with no Angle constructor, will yield an error since GHC cannot figure out which sort of angle you want to use. In this common situation you can use rotateBy, which interprets its argument as a number of turns.