Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Z = Z
- data tail :. head = tail :. head
- type DIM0 = Z
- type DIM1 = DIM0 :. Data Length
- type DIM2 = DIM1 :. Data Length
- type DIM3 = DIM2 :. Data Length
- class Shape sh where
- data All = All
- data Any sh = Any
- type family FullShape ss
- type family SliceShape ss
- class Slice ss where
- sliceOfFull :: ss -> FullShape ss -> SliceShape ss
- fullOfSlice :: ss -> SliceShape ss -> FullShape ss
- data Vector sh a = Vector sh (sh -> a)
- type DVector sh a = Vector sh (Data a)
- fromVector :: (Shape sh, Type a) => DVector sh a -> Data [a]
- toVector :: (Shape sh, Type a) => sh -> Data [a] -> DVector sh a
- freezeVector :: (Shape sh, Type a) => DVector sh a -> (Data [Length], Data [a])
- fromList :: Type a => [Data a] -> Data [a]
- thawVector :: (Shape sh, Type a) => (Data [Length], Data [a]) -> DVector sh a
- memorize :: (Shape sh, Type a) => DVector sh a -> DVector sh a
- extent :: Vector sh a -> sh
- newExtent :: sh -> Vector sh a -> Vector sh a
- traverse :: (Shape sh, Shape sh') => Vector sh a -> (sh -> sh') -> ((sh -> a) -> sh' -> a') -> Vector sh' a'
- replicate :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl)) => sl -> Vector (SliceShape sl) a -> Vector (FullShape sl) a
- slice :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl)) => Vector (FullShape sl) a -> sl -> Vector (SliceShape sl) a
- reshape :: (Shape sh, Shape sh') => sh -> Vector sh' a -> Vector sh a
- unit :: a -> Vector Z a
- (!:) :: Shape sh => Vector sh a -> sh -> a
- diagonal :: Vector DIM2 a -> Vector DIM1 a
- backpermute :: (Shape sh, Shape sh') => sh' -> (sh' -> sh) -> Vector sh a -> Vector sh' a
- map :: (a -> b) -> Vector sh a -> Vector sh b
- zip :: Shape sh => Vector sh a -> Vector sh b -> Vector sh (a, b)
- zipWith :: Shape sh => (a -> b -> c) -> Vector sh a -> Vector sh b -> Vector sh c
- fold :: (Shape sh, Syntax a) => (a -> a -> a) -> a -> Vector (sh :. Data Length) a -> Vector sh a
- fold' :: (Shape sh, Syntax a) => (a -> a -> a) -> Vector sh a -> Vector (sh :. Data Length) a -> Vector sh a
- sum :: (Shape sh, Type a, Numeric a) => DVector (sh :. Data Length) a -> DVector sh a
- (...) :: Data Index -> Data Index -> DVector DIM1 Index
- stencil :: DVector DIM2 Float -> DVector DIM2 Float
- laplace :: Data Length -> DVector DIM2 Float -> DVector DIM2 Float
- transpose2D :: Vector DIM2 e -> Vector DIM2 e
- mmMult :: (Type e, Numeric e) => DVector DIM2 e -> DVector DIM2 e -> DVector DIM2 e
- mapDIM1 :: (Data Index -> Data Index) -> DIM1 -> DIM1
- indexed :: Data Length -> (Data Index -> a) -> Vector DIM1 a
- length :: Vector DIM1 a -> Data Length
- newLen :: Syntax a => Data Length -> Vector DIM1 a -> Vector DIM1 a
- (++) :: Syntax a => Vector DIM1 a -> Vector DIM1 a -> Vector DIM1 a
- take :: Data Length -> Vector DIM1 a -> Vector DIM1 a
- drop :: Data Length -> Vector DIM1 a -> Vector DIM1 a
- splitAt :: Data Index -> Vector DIM1 a -> (Vector DIM1 a, Vector DIM1 a)
- head :: Syntax a => Vector DIM1 a -> a
- last :: Syntax a => Vector DIM1 a -> a
- tail :: Vector DIM1 a -> Vector DIM1 a
- init :: Vector DIM1 a -> Vector DIM1 a
- tails :: Vector DIM1 a -> Vector DIM1 (Vector DIM1 a)
- inits :: Vector DIM1 a -> Vector DIM1 (Vector DIM1 a)
- inits1 :: Vector DIM1 a -> Vector DIM1 (Vector DIM1 a)
- permute :: (Data Length -> Data Index -> Data Index) -> Vector DIM1 a -> Vector DIM1 a
- reverse :: Syntax a => Vector DIM1 a -> Vector DIM1 a
- rotateVecL :: Syntax a => Data Index -> Vector DIM1 a -> Vector DIM1 a
- rotateVecR :: Syntax a => Data Index -> Vector DIM1 a -> Vector DIM1 a
- replicate1 :: Data Length -> a -> Vector DIM1 a
- enumFromTo :: Data Index -> Data Index -> Vector DIM1 (Data Index)
- enumFrom :: Data Index -> Vector DIM1 (Data Index)
- unzip :: Vector DIM1 (a, b) -> (Vector DIM1 a, Vector DIM1 b)
- foldl :: Syntax a => (a -> b -> a) -> a -> Vector DIM1 b -> a
- fold1 :: Syntax a => (a -> a -> a) -> Vector DIM1 a -> a
- sum1 :: (Syntax a, Num a) => Vector DIM1 a -> a
- maximum :: Ord a => Vector DIM1 (Data a) -> Data a
- minimum :: Ord a => Vector DIM1 (Data a) -> Data a
- scalarProd :: (Syntax a, Num a) => Vector DIM1 a -> Vector DIM1 a -> a
- tVec :: Patch a a -> Patch (Vector DIM1 a) (Vector DIM1 a)
- tVec1 :: Patch a a -> Patch (Vector DIM1 (Data a)) (Vector DIM1 (Data a))
- tVec2 :: Patch a a -> Patch (Vector DIM2 (Data a)) (Vector DIM2 (Data a))
Documentation
data tail :. head infixl 3 Source
tail :. head infixl 3 |
Slice sl => Slice ((:.) sl All) | |
Slice sl => Slice ((:.) sl (Data Length)) | |
Shape sh => Shape ((:.) sh (Data Length)) | |
type SliceShape ((:.) sl All) = (:.) (SliceShape sl) (Data Length) | |
type SliceShape ((:.) sl (Data Length)) = SliceShape sl | |
type FullShape ((:.) sl All) = (:.) (FullShape sl) (Data Length) | |
type FullShape ((:.) sl (Data Length)) = (:.) (FullShape sl) (Data Length) |
Get the number of dimensions in a shape
The shape of an array of size zero, with a particular dimension
The shape of an array with size one, with a particular dimension
size :: sh -> Data Length Source
Get the total number of elements in an array with this shape.
toIndex :: sh -> sh -> Data Index Source
Index into flat, linear, row-major representation
fromIndex :: sh -> Data Index -> sh Source
Inverse of toIndex
.
intersectDim :: sh -> sh -> sh Source
The intersection of two dimensions.
inRange :: sh -> sh -> sh -> Data Bool Source
Check whether an index is within a given shape.
inRange l u i
checks that i
fits between l
and u
.
toList :: sh -> [Data Length] Source
Turn a shape into a list. Used in the Syntactic
instance.
toShape :: Int -> Data [Length] -> sh Source
Reconstruct a shape. Used in the Syntactic
instance.
- Slices
type family SliceShape ss Source
type SliceShape Z = Z | |
type SliceShape (Any sh) = sh | |
type SliceShape ((:.) sl All) = (:.) (SliceShape sl) (Data Length) | |
type SliceShape ((:.) sl (Data Length)) = SliceShape sl |
sliceOfFull :: ss -> FullShape ss -> SliceShape ss Source
fullOfSlice :: ss -> SliceShape ss -> FullShape ss Source
- Vectors
Vector sh (sh -> a) |
(Shape sh, Syntax a) => Syntactic (Vector sh a) | |
(Syntax a, Shape sh) => Sized (Vector sh a) | |
Syntax a => Indexed (Vector sh a) | |
CollMap (Vector sh a) (Vector sh a) | |
type Internal (Vector sh a) = ([Length], [Internal a]) | |
type Domain (Vector sh a) = FeldDomain | |
type CollSize (Vector sh a) = sh | |
type CollIndex (Vector sh a) = sh | |
type Elem (Vector sh a) = a |
fromVector :: (Shape sh, Type a) => DVector sh a -> Data [a] Source
- Fuctions
Store a vector in an array.
toVector :: (Shape sh, Type a) => sh -> Data [a] -> DVector sh a Source
Restore a vector from an array
memorize :: (Shape sh, Type a) => DVector sh a -> DVector sh a Source
Store a vector in memory. Use this function instead of force
if
possible as it is both much more safe and faster.
newExtent :: sh -> Vector sh a -> Vector sh a Source
Change the extent of the vector to the supplied value. If the supplied extent will contain more elements than the old extent, the new elements will have undefined value.
traverse :: (Shape sh, Shape sh') => Vector sh a -> (sh -> sh') -> ((sh -> a) -> sh' -> a') -> Vector sh' a' Source
Change shape and transform elements of a vector. This function is the most general way of manipulating a vector.
replicate :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl)) => sl -> Vector (SliceShape sl) a -> Vector (FullShape sl) a Source
Duplicates part of a vector along a new dimension.
slice :: (Slice sl, Shape (FullShape sl), Shape (SliceShape sl)) => Vector (FullShape sl) a -> sl -> Vector (SliceShape sl) a Source
Extracts a slice from a vector.
reshape :: (Shape sh, Shape sh') => sh -> Vector sh' a -> Vector sh a Source
Change the shape of a vector. This function is potentially unsafe, the new shape need to have fewer or equal number of elements compared to the old shape.
backpermute :: (Shape sh, Shape sh') => sh' -> (sh' -> sh) -> Vector sh a -> Vector sh' a Source
Change the shape of a vector.
zip :: Shape sh => Vector sh a -> Vector sh b -> Vector sh (a, b) Source
Combines the elements of two vectors. The size of the resulting vector will be the intersection of the two argument vectors.
zipWith :: Shape sh => (a -> b -> c) -> Vector sh a -> Vector sh b -> Vector sh c Source
Combines the elements of two vectors pointwise using a function. The size of the resulting vector will be the intersection of the two argument vectors.
fold :: (Shape sh, Syntax a) => (a -> a -> a) -> a -> Vector (sh :. Data Length) a -> Vector sh a Source
Reduce a vector along its last dimension
fold' :: (Shape sh, Syntax a) => (a -> a -> a) -> Vector sh a -> Vector (sh :. Data Length) a -> Vector sh a Source
A generalization of fold
which allows for different initial
values when starting to fold.
sum :: (Shape sh, Type a, Numeric a) => DVector (sh :. Data Length) a -> DVector sh a Source
Summing a vector along its last dimension
mmMult :: (Type e, Numeric e) => DVector DIM2 e -> DVector DIM2 e -> DVector DIM2 e Source
Matrix multiplication
Operations on one dimensional vectors
newLen :: Syntax a => Data Length -> Vector DIM1 a -> Vector DIM1 a Source
Change the length of the vector to the supplied value. If the supplied length is greater than the old length, the new elements will have undefined value. The resulting vector has only one segment.
permute :: (Data Length -> Data Index -> Data Index) -> Vector DIM1 a -> Vector DIM1 a Source
Permute a vector
enumFromTo :: Data Index -> Data Index -> Vector DIM1 (Data Index) Source
enumFromTo m n
: Enumerate the indexes from m
to n
In order to enumerate a different type, use i2n
, e.g:
map i2n (10...20) :: Vector1 Word8
enumFrom :: Data Index -> Vector DIM1 (Data Index) Source
enumFrom m
: Enumerate the indexes from m
to maxBound
foldl :: Syntax a => (a -> b -> a) -> a -> Vector DIM1 b -> a Source
Corresponds to the standard foldl
.