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

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

Diagrams.TwoD.Types

Contents

Description

Basic types for two-dimensional Euclidean space.

Synopsis

2D Euclidean space

data V2 a :: * -> *

A 2-dimensional vector

>>> pure 1 :: V2 Int
V2 1 1
>>> V2 1 2 + V2 3 4
V2 4 6
>>> V2 1 2 * V2 3 4
V2 3 8
>>> sum (V2 1 2)
3

Constructors

V2 !a !a 

Instances

Monad V2 
Functor V2 
MonadFix V2 
Applicative V2 
Foldable V2 
Traversable V2 
Generic1 V2 
Apply V2 
Distributive V2 
Representable V2 
MonadZip V2 
Serial1 V2 
Additive V2 
Traversable1 V2 
Affine V2 
R2 V2 
R1 V2 
Metric V2 
Foldable1 V2 
Bind V2 
Eq1 V2 
Ord1 V2 
Read1 V2 
Show1 V2 
HasTheta V2 
HasR V2 
Unbox a => Vector Vector (V2 a) 
Unbox a => MVector MVector (V2 a) 
Bounded a => Bounded (V2 a) 
Eq a => Eq (V2 a) 
Floating a => Floating (V2 a) 
Fractional a => Fractional (V2 a) 
Data a => Data (V2 a) 
Num a => Num (V2 a) 
Ord a => Ord (V2 a) 
Read a => Read (V2 a) 
Show a => Show (V2 a) 
Ix a => Ix (V2 a) 
Generic (V2 a) 
Storable a => Storable (V2 a) 
Binary a => Binary (V2 a) 
Serial a => Serial (V2 a) 
Serialize a => Serialize (V2 a) 
NFData a => NFData (V2 a) 
Transformable (V2 n) 
Hashable a => Hashable (V2 a) 
Unbox a => Unbox (V2 a) 
Ixed (V2 a) 
Epsilon a => Epsilon (V2 a) 
Coordinates (V2 n) 
FunctorWithIndex (E V2) V2 
FoldableWithIndex (E V2) V2 
TraversableWithIndex (E V2) V2 
Each (V2 a) (V2 b) a b 
OrderedField n => Traced (FixedSegment V2 n) 
RealFloat n => Traced (Trail V2 n) 
RealFloat n => Traced (Path V2 n) 
RealFloat n => Traced (BoundingBox V2 n) 
Typeable (* -> *) V2 
OrderedField n => Traced (Segment Closed V2 n) 
(TypeableFloat n, Renderable (Path V2 n) b) => TrailLike (QDiagram b V2 n Any) 
type Rep1 V2 = D1 D1V2 (C1 C1_0V2 ((:*:) (S1 NoSelector Par1) (S1 NoSelector Par1))) 
type Rep V2 = E V2 
type Diff V2 = V2 
data MVector s (V2 a) = MV_V2 !Int (MVector s a) 
type Rep (V2 a) = D1 D1V2 (C1 C1_0V2 ((:*:) (S1 NoSelector (Rec0 a)) (S1 NoSelector (Rec0 a)))) 
type V (V2 n) = V2 
type N (V2 n) = n 
data Vector (V2 a) = V_V2 !Int (Vector a) 
type Index (V2 a) = E V2 
type IxValue (V2 a) = a 
type FinalCoord (V2 n) = n 
type PrevDim (V2 n) = n 
type Decomposition (V2 n) = (:&) n n 

class R1 t where

A space that has at least 1 basis vector _x.

Minimal complete definition

Nothing

Methods

_x :: Functor f => (a -> f a) -> t a -> f (t a)

>>> V1 2 ^._x
2
>>> V1 2 & _x .~ 3
V1 3

Instances

R1 Identity 
R1 V4 
R1 V3 
R1 V2 
R1 V1 
R1 f => R1 (Point f) 

class R1 t => R2 t where

A space that distinguishes 2 orthogonal basis vectors _x and _y, but may have more.

Minimal complete definition

Nothing

Methods

_y :: Functor f => (a -> f a) -> t a -> f (t a)

>>> V2 1 2 ^._y
2
>>> V2 1 2 & _y .~ 3
V2 1 3

_xy :: Functor f => (V2 a -> f (V2 a)) -> t a -> f (t a)

Instances

R2 V4 
R2 V3 
R2 V2 
R2 f => R2 (Point f) 

type P2 = Point V2 Source

r2 :: (n, n) -> V2 n Source

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

unr2 :: V2 n -> (n, n) Source

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

mkR2 :: n -> n -> V2 n Source

Curried form of r2.

r2Iso :: Iso' (V2 n) (n, n) Source

p2 :: (n, n) -> P2 n Source

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

mkP2 :: n -> n -> P2 n Source

Curried form of p2.

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

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

p2Iso :: Iso' (Point V2 n) (n, n) Source

r2PolarIso :: RealFloat n => Iso' (V2 n) (n, Angle n) Source

class HasR t where Source

A space which has magnitude _r that can be calculated numerically.

Minimal complete definition

Nothing

Methods

_r :: RealFloat n => Lens' (t n) n Source

Instances

HasR V3 
HasR V2 
HasR v => HasR (Point v)