| Maintainer | diagrams-discuss@googlegroups.com |
|---|---|
| Safe Haskell | None |
Diagrams.TwoD.Types
Contents
Description
Basic types for two-dimensional Euclidean space.
- data R2 = R2 !Double !Double
- r2 :: (Double, Double) -> R2
- unr2 :: R2 -> (Double, Double)
- mkR2 :: Double -> Double -> R2
- r2Iso :: Iso' R2 (Double, Double)
- type P2 = Point R2
- p2 :: (Double, Double) -> P2
- mkP2 :: Double -> Double -> P2
- unp2 :: P2 -> (Double, Double)
- p2Iso :: Iso' P2 (Double, Double)
- type T2 = Transformation R2
- class Num a => Angle a where
- newtype Turn = Turn Double
- asTurn :: Turn -> Turn
- type CircleFrac = Turn
- newtype Rad = Rad Double
- asRad :: Rad -> Rad
- newtype Deg = Deg Double
- asDeg :: Deg -> Deg
- fullTurn :: Angle a => a
- fullCircle :: Angle a => a
- convertAngle :: (Angle a, Angle b) => a -> b
- angleRatio :: Angle a => a -> a -> Double
2D Euclidean space
The two-dimensional Euclidean vector space R^2. This type is intentionally abstract.
- To construct a vector, use
r2, or^&(from Diagrams.Coordinates):
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, usep..-.origin - To convert a vector
vinto the point obtained by followingvfrom the origin, use.origin.+^v - To convert a vector back into a pair of components, use
unv2orcoords(from Diagrams.Coordinates). These are typically used in conjunction with theViewPatternsextension:
foo (unr2 -> (x,y)) = ... foo (coords -> x :& y) = ...
Instances
| Eq R2 | |
| Fractional R2 | |
| Num R2 | |
| Ord R2 | |
| Read R2 | |
| Show R2 | |
| Typeable R2 | |
| Transformable R2 | |
| HasBasis R2 | |
| VectorSpace R2 | |
| InnerSpace R2 | |
| AdditiveGroup R2 | |
| HasY P2 | |
| HasY R2 | |
| HasX P2 | |
| HasX R2 | |
| Coordinates R2 | |
| Traced (FixedSegment R2) | |
| Traced (Trail R2) | |
| Traced (Path R2) | |
| Wrapped [Path R2] [Path R2] Clip Clip | |
| Traced (Segment Closed R2) | |
| Wrapped (Double, Double) (Double, Double) R2 R2 | Lens wrapped isomorphisms for R2. |
| Renderable (Path R2) b => TrailLike (QDiagram b R2 Any) |
unr2 :: R2 -> (Double, Double)Source
Convert a 2D vector back into a pair of components. See also coords.
Points in R^2. This type is intentionally abstract.
- To construct a point, use
p2, or^&(see Diagrams.Coordinates):
p2 (3,4) :: P2 3 ^& 4 :: P2
- To construct a point from a vector
v, use.origin.+^v - To convert a point
pinto the vector from the origin top, usep..-.origin - To convert a point back into a pair of coordinates, use
unp2, orcoords(from Diagrams.Coordinates). It's common to use these in conjunction with theViewPatternsextension:
foo (unp2 -> (x,y)) = ... foo (coords -> x :& y) = ...
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
Convert to a turn, i.e. a fraction of a circle.
Convert from a turn, i.e. a fraction of a circle.
Newtype wrapper used to represent angles as fractions of a circle. For example, 1/3 turn = tau/3 radians = 120 degrees.
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 wrapper for representing angles in radians.
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 wrapper for representing angles in degrees.
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.
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