hgeometry-0.5.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.Geometry.Vector.VectorFixed

Contents

Synopsis

Documentation

data C n Source

A proxy which can be used for the coordinates.

Constructors

C 

Instances

Eq (C n) Source 
Ord (C n) Source 
Read (C n) Source 
Show (C n) Source 

d dimensional Vectors

newtype Vector d r Source

Datatype representing d dimensional vectors. Our implementation wraps the implementation provided by fixed-vector.

Constructors

Vector 

Fields

_unV :: Vec (ToPeano d) r
 

Instances

Arity d => Functor (Vector d) Source 
Arity d => Applicative (Vector d) Source 
Arity d => Foldable (Vector d) Source 
Arity d => Traversable (Vector d) Source 
Arity d => Affine (Vector d) Source 
Arity d => Metric (Vector d) Source 
Arity d => Additive (Vector d) Source 
Arity d => Vector (Vector d) r Source 
(Eq r, Arity d) => Eq (Vector d r) Source 
(Ord r, Arity d) => Ord (Vector d r) Source 
(Show r, Arity d) => Show (Vector d r) Source 
type Dim (Vector d) = ToPeano d Source 
type Diff (Vector d) = Vector d Source 

unV :: Lens' (Vector d r) (Vec (ToPeano d) r) Source

type Arity n = Arity (ToPeano n) Source

type Index' i d = Index (ToPeano i) (ToPeano d) Source

element :: forall proxy i d r. (Arity d, Index' i d) => proxy i -> Lens' (Vector d r) r Source

Lens into the i th element

element' :: forall d r. (KnownNat d, Arity d) => Int -> Traversal' (Vector d r) r Source

Similar to element above. Except that we don't have a static guarantee that the index is in bounds. Hence, we can only return a Traversal

type AlwaysTrueDestruct pd d = (Arity pd, ToPeano d ~ S (ToPeano pd)) Source

destruct :: AlwaysTrueDestruct predD d => Vector d r -> (r, Vector predD r) Source

Get the head and tail of a vector

cross :: Num r => Vector 3 r -> Vector 3 r -> Vector 3 r Source

Cross product of two three-dimensional vectors

toV3 :: Vector 3 a -> V3 a Source

Conversion to a Linear.V3

fromV3 :: V3 a -> Vector 3 a Source

Conversion from a Linear.V3

type AlwaysTrueSnoc d = ToPeano (1 + d) ~ S (ToPeano d) Source

snoc :: (AlwaysTrueSnoc d, Arity d) => Vector d r -> r -> Vector (1 + d) r Source

Add an element at the back of the vector

init :: AlwaysTrueDestruct predD d => Vector d r -> Vector predD r Source

Get a vector of the first d - 1 elements.

prefix :: Prefix (ToPeano i) (ToPeano d) => Vector d r -> Vector i r Source

Get a prefix of i elements of a vector

class Prefix i d where Source

Methods

prefix' :: Vec d r -> Vec i r Source

Instances

Prefix Z d Source 
(Arity i, Arity d, Index i d, Prefix i d) => Prefix (S i) (S d) Source 

imap :: Arity d => (Int -> r -> s) -> Vector d r -> Vector d s Source

Map with indices

Functions specific to two and three dimensional vectors.

v2 :: r -> r -> Vector 2 r Source

Construct a 2 dimensional vector

v3 :: r -> r -> r -> Vector 3 r Source

Construct a 3 dimensional vector

_unV2 :: Vector 2 r -> (r, r) Source

Destruct a 2 dim vector into a pair

_unV3 :: Vector 3 r -> (r, r, r) Source

pattern Vector2 :: r -> r -> Vector 2 r Source

Pattern synonym for two and three dim vectors

pattern Vector3 :: r -> r -> r -> Vector 3 r Source