Safe Haskell | None |
---|
- data a :. b = !a :. !b
- class ShowVec v where
- type Vec2 a = a :. (a :. ())
- type Vec3 a = a :. Vec2 a
- type Vec4 a = a :. Vec3 a
- type Vec5 a = a :. Vec4 a
- type Vec6 a = a :. Vec5 a
- type Vec7 a = a :. Vec6 a
- type Vec8 a = a :. Vec7 a
- type Vec9 a = a :. Vec8 a
- type Vec10 a = a :. Vec9 a
- type Vec11 a = a :. Vec10 a
- type Vec12 a = a :. Vec11 a
- type Vec13 a = a :. Vec12 a
- type Vec14 a = a :. Vec13 a
- type Vec15 a = a :. Vec14 a
- type Vec16 a = a :. Vec15 a
- type Vec17 a = a :. Vec16 a
- type Vec18 a = a :. Vec17 a
- type Vec19 a = a :. Vec18 a
- class Vec n a v | n a -> v, v -> n a where
- mkVec :: n -> a -> v
- vec :: Vec n a v => a -> v
- class VecList a v | v -> a where
- class Access n a v | v -> a where
- class Head v a | v -> a where
- head :: v -> a
- class Tail v v_ | v -> v_ where
- tail :: v -> v_
- class Map a b u v | u -> a, v -> b, b u -> v, a v -> u where
- map :: (a -> b) -> u -> v
- class ZipWith a b c u v w | u -> a, v -> b, w -> c, u v c -> w where
- zipWith :: (a -> b -> c) -> u -> v -> w
- class Fold v a | v -> a where
- reverse :: Reverse' () v v' => v -> v'
- class Reverse' p v v' | p v -> v' where
- reverse' :: p -> v -> v'
- class Append v1 v2 v3 | v1 v2 -> v3, v1 v3 -> v2 where
- append :: v1 -> v2 -> v3
- class Take n v v' | n v -> v' where
- take :: n -> v -> v'
- class Drop n v v' | n v -> v' where
- drop :: n -> v -> v'
- class Last v a | v -> a where
- last :: v -> a
- class Snoc v a v' | v a -> v', v' -> v a where
- snoc :: v -> a -> v'
- class Length v n | v -> n where
- sum :: (Fold v a, Num a) => v -> a
- product :: (Fold v a, Num a) => v -> a
- maximum :: (Fold v a, Ord a) => v -> a
- minimum :: (Fold v a, Ord a) => v -> a
- toList :: Fold v a => v -> [a]
- type Mat22 a = Vec2 (Vec2 a)
- type Mat23 a = Vec2 (Vec3 a)
- type Mat24 a = Vec2 (Vec4 a)
- type Mat32 a = Vec3 (Vec2 a)
- type Mat33 a = Vec3 (Vec3 a)
- type Mat34 a = Vec3 (Vec4 a)
- type Mat35 a = Vec3 (Vec5 a)
- type Mat36 a = Vec3 (Vec6 a)
- type Mat42 a = Vec4 (Vec2 a)
- type Mat43 a = Vec4 (Vec3 a)
- type Mat44 a = Vec4 (Vec4 a)
- type Mat45 a = Vec4 (Vec5 a)
- type Mat46 a = Vec4 (Vec6 a)
- type Mat47 a = Vec4 (Vec7 a)
- type Mat48 a = Vec4 (Vec8 a)
- matToLists :: (Fold v a, Fold m v) => m -> [[a]]
- matToList :: (Fold v a, Fold m v) => m -> [a]
- matFromLists :: (Vec j a v, Vec i v m, VecList a v, VecList v m) => [[a]] -> m
- matFromList :: forall i j v m a. (Vec i v m, Vec j a v, Nat i, VecList a v, VecList v m) => [a] -> m
- sizeOf# :: Storable a => a -> Int#
- class VecArrayRW v where
Documentation
The vector constructor. (:.)
for vectors is like (:)
for lists, and
()
takes the place of []
. (The list of instances here is not meant to be
readable.)
!a :. !b |
Vector Types
class Vec n a v | n a -> v, v -> n a whereSource
The type constraint Vec n a v
infers the vector type v
from the
length n
, a type-level natural, and underlying component type a
.
So x :: Vec N4 a v => v
declares x
to be a 4-vector of a
s.
Make a uniform vector of a given length. n
is a type-level natural.
Use vec
when the length can be inferred.
class VecList a v | v -> a whereSource
Build a vector from a list, or access vector elements using run-time indicies, numbered from 0.
Turn a list into a vector of inferred length. The list must be at least
as long as the vector, but may be longer. Make a mental note of the
distinction between this and matFromList
, as you might accidentally use
this when you mean that. Because number literals can be converted to
vectors, and matrices are vectors of vectors, the following works
fromList [1,2,3,4] :: Mat22 Int > ((1):.(1):.()):.((2):.(2):.()):.()
even though we meant to do this
matFromList [1,2,3,4] :: Mat22 Int > ((1):.(2):.()):.((3):.(4):.()):.()
getElem :: Int -> v -> aSource
Get a vector element, which one determined at runtime.
setElem :: Int -> a -> v -> vSource
Set a vector element, which one determined at runtime
class Access n a v | v -> a whereSource
get or set a vector element, known at compile
time. Use the Nat types to access vector components. For instance, get n0
gets the x component, set n2 44
sets the z component to 44.
List-like functions
class Map a b u v | u -> a, v -> b, b u -> v, a v -> u whereSource
Apply a function over each element in a vector. Constraint Map a b u v
states that u
is a vector of a
s, v
is a vector of b
s with the same
length as u
, and the function is of type a -> b
.
class ZipWith a b c u v w | u -> a, v -> b, w -> c, u v c -> w whereSource
Combine two vectors using a binary function. The length of the result is
the min of the lengths of the arguments. The constraint ZipWith a b c u v
w
states that u
is a vector of a
s, v
is a vector of b
s, w
is a
vector of c
s, and the binary function is of type a -> b -> c
.
(ZipWith a b c u v w, PackedVec u, PackedVec v, PackedVec w) => ZipWith a b c (Packed u) (Packed v) (Packed w) | |
ZipWith a b c (:. a' u) (:. b' v) (:. c' w) => ZipWith a b c (:. a (:. a' u)) (:. b (:. b' v)) (:. c (:. c' w)) | |
ZipWith a b c (:. a (:. a as)) (:. b ()) (:. c ()) | |
ZipWith a b c (:. a ()) (:. b (:. b bs)) (:. c ()) | |
ZipWith a b c (:. a ()) (:. b ()) (:. c ()) |
class Fold v a | v -> a whereSource
Fold a function over a vector.
class Reverse' p v v' | p v -> v' whereSource
Reverse helper function : accumulates the reversed list in its first argument
class Take n v v' | n v -> v' whereSource
take n v
constructs a vector from the first n
elements of v
. n
is a
type-level natural. For example take n3 v
makes a 3-vector of the first
three elements of v
.
class Drop n v v' | n v -> v' whereSource
drop n v
strips the first n
elements from v
. n
is a type-level
natural. For example drop n2 v
drops the first two elements.
class Last v a | v -> a whereSource
Get the last element, usually significant for some reason (quaternions, homogenous coordinates, whatever)
Matrix Types
matToLists :: (Fold v a, Fold m v) => m -> [[a]]Source
convert a matrix to a list-of-lists
matFromLists :: (Vec j a v, Vec i v m, VecList a v, VecList v m) => [[a]] -> mSource
convert a list-of-lists into a matrix
matFromList :: forall i j v m a. (Vec i v m, Vec j a v, Nat i, VecList a v, VecList v m) => [a] -> mSource
convert a list into a matrix. (row-major order)
class VecArrayRW v whereSource
vaRead# :: MutableByteArray# s# -> Int# -> State# s# -> (#State# s#, v#)Source
vaWrite# :: MutableByteArray# s# -> Int# -> v -> State# s# -> State# s#Source
vaIndex# :: ByteArray# -> Int# -> vSource
VecArrayRW (:. Double ()) | |
VecArrayRW (:. Double v) => VecArrayRW (:. Double (:. Double v)) | |
VecArrayRW (:. Float ()) | |
VecArrayRW (:. Float v) => VecArrayRW (:. Float (:. Float v)) | |
VecArrayRW (:. Int ()) | |
VecArrayRW (:. Int v) => VecArrayRW (:. Int (:. Int v)) | |
VecArrayRW (:. Word8 ()) | |
VecArrayRW (:. Word8 v) => VecArrayRW (:. Word8 (:. Word8 v)) |