Vec-0.9.2: Fixed-length lists and low-dimensional linear algebra.Source codeContentsIndex
Data.Vec.Packed
Description

Packed vectors : use these whenever possible. The generic vector type is is represented at run-time by a linked list of boxed values. Packed types, however, store the vector components sequentially in memory. Vector operations can be defined using the generic types, and the compiler will inline and specialize these definitions for the packed types, avoiding any list cells or unnecessary heap allocations.

Packed vectors are related to their unpacked representations by way of an associated type. An instance of class PackedVec v declares that v has a packed representation, and the type of that is Packed v. The packed constructors are named VecNT where N is 2, 3 or 4 and T is I, F or D for Int, Float or Double. So the expression Vec3D x y z constructs a packed 3-vector of Doubles, the type of which is Packed (Vec3 Double). The constructor name is also a synonym for the packed type name, i.e., type Vec3D = Packed (Vec3 Double), so the packed type acts as if it had been declared data Vec3D = Vec3D x y z.

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. Some functions, like multmv, do not need their arguments to be unpacked, but the result is a polymorphic vector (:.), so you will need to pack it again. I admit that this is awkward.

There are also instances for Take, Drop, Last, Head, Tail and Snoc. These come in handy for thinks like quaternions and homogenous coordinates.

Synopsis
class PackedVec v where
data Packed v
pack :: v -> Packed v
unpack :: Packed v -> v
type Vec2I = Packed (Vec2 Int)
type Vec3I = Packed (Vec3 Int)
type Vec4I = Packed (Vec4 Int)
type Vec2F = Packed (Vec2 Float)
type Vec3F = Packed (Vec3 Float)
type Vec4F = Packed (Vec4 Float)
type Vec2D = Packed (Vec2 Double)
type Vec3D = Packed (Vec3 Double)
type Vec4D = Packed (Vec4 Double)
type Mat22D = Vec2 Vec2D
type Mat23D = Vec2 Vec3D
type Mat24D = Vec2 Vec4D
type Mat33D = Vec3 Vec3D
type Mat34D = Vec3 Vec4D
type Mat44D = Vec4 Vec4D
packMat :: (Map row (Packed row) mat packedMat, PackedVec row) => mat -> packedMat
unpackMat :: (Map (Packed row) row packedMat mat, PackedVec row) => packedMat -> mat
Documentation
class PackedVec v whereSource
PackedVec class : relates a vector type to its space-optimized representation.
Associated Types
data Packed v Source
The packed representation of v
Methods
pack :: v -> Packed vSource
unpack :: Packed v -> vSource
show/hide Instances
type Vec2I = Packed (Vec2 Int)Source
type Vec3I = Packed (Vec3 Int)Source
type Vec4I = Packed (Vec4 Int)Source
type Vec2F = Packed (Vec2 Float)Source
type Vec3F = Packed (Vec3 Float)Source
type Vec4F = Packed (Vec4 Float)Source
type Vec2D = Packed (Vec2 Double)Source
type Vec3D = Packed (Vec3 Double)Source
type Vec4D = Packed (Vec4 Double)Source
type Mat22D = Vec2 Vec2DSource
type Mat23D = Vec2 Vec3DSource
type Mat24D = Vec2 Vec4DSource
type Mat33D = Vec3 Vec3DSource
type Mat34D = Vec3 Vec4DSource
type Mat44D = Vec4 Vec4DSource
packMat :: (Map row (Packed row) mat packedMat, PackedVec row) => mat -> packedMatSource
Construct a semi-packed matrix, one whose rows are packed.
unpackMat :: (Map (Packed row) row packedMat mat, PackedVec row) => packedMat -> matSource
Produced by Haddock version 2.3.0