Safe Haskell | None |
---|
Packed vectors : use these whenever possible. The polymorphic vector type
is represented at run-time by a linked list of boxed values. Specialized, or
packed types, store the vector components sequentially in memory, in a
single boxed value. Definitions for vector operations, given in terms of
polymorphic vectors, can be (almost) automatically propagated to packed
types using the functions pack
and unpack
. The compiler can then
specialize the definition to the packed type and produce efficient code.
Packed vectors are related to their unpacked representations by way of an
associated type. An instance of class
declares that PackedVec
vv
has
a packed representation, and the type of that is
. The packed
constructors are named Packed
vVec
NT 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,
does not require pack/unpack because it is defined in
terms of dot
and zipWith
. However fold
, transpose
,
det
and most others are recursive (i.e., defined in terms of the
same operation on lower-dimensional vectors), and so you'll still need to
use pack/unpack with these. This goes for gaussElim
as well because it uses
multmm
. Some functions, like transpose
, do not need their arguments
to be unpacked, but the result is a polymorphic vector multmv
(:.)
, so you will
need to pack it again. I admit that this is awkward, and I'm still looking
for a better way.
There are also instances for Access
, Take
, Drop
, Last
, Head
,
Tail
and Snoc
. These come in handy for things like quaternions and
homogenous coordinates.
- class PackedVec v where
- type Vec2B = Packed (Vec2 Bool)
- type Vec3B = Packed (Vec3 Bool)
- type Vec4B = Packed (Vec4 Bool)
- 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 Vec2CF = Packed (Vec2 CFloat)
- type Vec3CF = Packed (Vec3 CFloat)
- type Vec4CF = Packed (Vec4 CFloat)
- type Vec2CI = Packed (Vec2 CInt)
- type Vec3CI = Packed (Vec3 CInt)
- type Vec4CI = Packed (Vec4 CInt)
- type Vec2CD = Packed (Vec2 CDouble)
- type Vec3CD = Packed (Vec3 CDouble)
- type Vec4CD = Packed (Vec4 CDouble)
- 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
PackedVec class : relates a vector type to its space-optimized representation.
PackedVec (Vec4 Bool) | |
PackedVec (Vec4 Double) | |
PackedVec (Vec4 Float) | |
PackedVec (Vec4 Int) | |
PackedVec (Vec4 CInt) | |
PackedVec (Vec4 CFloat) | |
PackedVec (Vec4 CDouble) | |
PackedVec (Vec3 Bool) | |
PackedVec (Vec3 Double) | |
PackedVec (Vec3 Float) | |
PackedVec (Vec3 Int) | |
PackedVec (Vec3 CInt) | |
PackedVec (Vec3 CFloat) | |
PackedVec (Vec3 CDouble) | |
PackedVec (Vec2 Bool) | |
PackedVec (Vec2 Double) | |
PackedVec (Vec2 Float) | |
PackedVec (Vec2 Int) | |
PackedVec (Vec2 CInt) | |
PackedVec (Vec2 CFloat) | |
PackedVec (Vec2 CDouble) |