Copyright | (c) 2013 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
Type for representing angles.
Synopsis
- data Angle n
- (@@) :: b -> AReview a b -> a
- rad :: Iso' (Angle n) n
- turn :: Floating n => Iso' (Angle n) n
- deg :: Floating n => Iso' (Angle n) n
- fullTurn :: Floating v => Angle v
- halfTurn :: Floating v => Angle v
- quarterTurn :: Floating v => Angle v
- sinA :: Floating n => Angle n -> n
- cosA :: Floating n => Angle n -> n
- tanA :: Floating n => Angle n -> n
- asinA :: Floating n => n -> Angle n
- acosA :: Floating n => n -> Angle n
- atanA :: Floating n => n -> Angle n
- atan2A :: RealFloat n => n -> n -> Angle n
- atan2A' :: OrderedField n => n -> n -> Angle n
- angleBetween :: (Metric v, Floating n, Ord n) => v n -> v n -> Angle n
- angleRatio :: Floating n => Angle n -> Angle n -> n
- normalizeAngle :: (Floating n, Real n) => Angle n -> Angle n
- class HasTheta t where
- class HasTheta t => HasPhi t where
- rotation :: Floating n => Angle n -> Transformation V2 n
- rotate :: (InSpace V2 n t, Transformable t, Floating n) => Angle n -> t -> t
Angle type
Angles can be expressed in a variety of units. Internally, they are represented in radians.
Instances
Functor Angle Source # | |
Applicative Angle Source # | |
Additive Angle Source # | |
Defined in Diagrams.Angle | |
Enum n => Enum (Angle n) Source # | |
Eq n => Eq (Angle n) Source # | |
Ord n => Ord (Angle n) Source # | |
Read n => Read (Angle n) Source # | |
Show n => Show (Angle n) Source # | |
Num n => Semigroup (Angle n) Source # | |
Num n => Monoid (Angle n) Source # | |
(V t ~ V2, N t ~ n, Transformable t, Floating n) => Action (Angle n) t Source # | Angles act on other things by rotation. |
Defined in Diagrams.Angle | |
type N (Angle n) Source # | |
Defined in Diagrams.Angle |
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. Angle
s 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
Common angles
quarterTurn :: Floating v => Angle v Source #
An angle representing a quarter turn.
Trigonometric functions
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 #
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.
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
.
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.
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 Iso
s 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.