Vec-0.9.1: Fixed-length lists and low-dimensional linear algebra.Source codeContentsIndex
Data.Vec.Packed
Contents
Packed Vector Types
Packed Matrix Types
Description

Packed vectors : use these whenever possible. The regular vector type is just a gussied up linked list, but when vector functions are applied to these types, bracketed by pack and unpack, then things unfold into neatly optimized code.

Storable, Num, Fractional, Fold, Map, and ZipWith instances are provided for packed vectors, so some operations do not require pack/unpack. For example, dot does not require pack/unpack because it is defined in terms of zipWith and fold. However transpose, det, gaussElim and most others are recursive, and so you'll still need to use pack/unpack with these. This goes for multmm as well because it uses transpose, and multmv does not need its arguments to be unpacked, but the result will be a polymorphic vector of type (:.), so you will want to pack it again. This is all very experimental and likely to change.

Synopsis
class PackedVec pv v | pv -> v where
pack :: v -> pv
unpack :: pv -> v
data Vec2I = Vec2I !!Int !!Int
data Vec3I = Vec3I !!Int !!Int !!Int
data Vec4I = Vec4I !!Int !!Int !!Int !!Int
data Vec2F = Vec2F !!Float !!Float
data Vec3F = Vec3F !!Float !!Float !!Float
data Vec4F = Vec4F !!Float !!Float !!Float !!Float
data Vec2D = Vec2D !!Double !!Double
data Vec3D = Vec3D !!Double !!Double !!Double
data Vec4D = Vec4D !!Double !!Double !!Double !!Double
type Mat22I = Vec2 Vec2I
type Mat23I = Vec2 Vec3I
type Mat33I = Vec3 Vec3I
type Mat34I = Vec3 Vec4I
type Mat44I = Vec4 Vec3I
type Mat22F = Vec2 Vec2F
type Mat23F = Vec2 Vec3F
type Mat33F = Vec3 Vec3F
type Mat34F = Vec3 Vec4F
type Mat44F = Vec4 Vec3F
type Mat22D = Vec2 Vec2D
type Mat23D = Vec2 Vec3D
type Mat33D = Vec3 Vec3D
type Mat34D = Vec3 Vec4D
type Mat44D = Vec4 Vec4D
packMat :: (Map v pv m pm, PackedVec pv v) => m -> pm
unpackMat :: (Map pv v pm m, PackedVec pv v) => pm -> m
Documentation
class PackedVec pv v | pv -> v whereSource
PackedVec class : relates a packed vector type to its unpacked type For now, the fundep is not bijective -- It may be advantageous to have multiple packed representations for a canonical vector type. This may change. In the meantime, you may have to annotate return types.
Methods
pack :: v -> pvSource
unpack :: pv -> vSource
show/hide Instances
Packed Vector Types
data Vec2I Source
Constructors
Vec2I !!Int !!Int
show/hide Instances
data Vec3I Source
Constructors
Vec3I !!Int !!Int !!Int
show/hide Instances
data Vec4I Source
Constructors
Vec4I !!Int !!Int !!Int !!Int
show/hide Instances
data Vec2F Source
Constructors
Vec2F !!Float !!Float
show/hide Instances
data Vec3F Source
Constructors
Vec3F !!Float !!Float !!Float
show/hide Instances
data Vec4F Source
Constructors
Vec4F !!Float !!Float !!Float !!Float
show/hide Instances
data Vec2D Source
Constructors
Vec2D !!Double !!Double
show/hide Instances
data Vec3D Source
Constructors
Vec3D !!Double !!Double !!Double
show/hide Instances
data Vec4D Source
Constructors
Vec4D !!Double !!Double !!Double !!Double
show/hide Instances
Packed Matrix Types
type Mat22I = Vec2 Vec2ISource
type Mat23I = Vec2 Vec3ISource
type Mat33I = Vec3 Vec3ISource
type Mat34I = Vec3 Vec4ISource
type Mat44I = Vec4 Vec3ISource
type Mat22F = Vec2 Vec2FSource
type Mat23F = Vec2 Vec3FSource
type Mat33F = Vec3 Vec3FSource
type Mat34F = Vec3 Vec4FSource
type Mat44F = Vec4 Vec3FSource
type Mat22D = Vec2 Vec2DSource
type Mat23D = Vec2 Vec3DSource
type Mat33D = Vec3 Vec3DSource
type Mat34D = Vec3 Vec4DSource
type Mat44D = Vec4 Vec4DSource
packMat :: (Map v pv m pm, PackedVec pv v) => m -> pmSource
pack a matrix
unpackMat :: (Map pv v pm m, PackedVec pv v) => pm -> mSource
unpack a matrix
Produced by Haddock version 2.3.0