Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Array a = A {}
- class Vector v
- type ShapeL = [Int]
- class Storable a
- type Unbox = Storable
- size :: Array a -> Int
- shapeL :: Array a -> ShapeL
- rank :: Array a -> Int
- toList :: (HasCallStack, Unbox a) => Array a -> [a]
- fromList :: (HasCallStack, Unbox a) => ShapeL -> [a] -> Array a
- toVector :: (HasCallStack, Unbox a) => Array a -> Vector a
- fromVector :: (HasCallStack, Unbox a) => ShapeL -> Vector a -> Array a
- normalize :: Unbox a => Array a -> Array a
- scalar :: Unbox a => a -> Array a
- unScalar :: (HasCallStack, Unbox a) => Array a -> a
- constant :: Unbox a => ShapeL -> a -> Array a
- reshape :: (HasCallStack, Unbox a) => ShapeL -> Array a -> Array a
- stretch :: HasCallStack => ShapeL -> Array a -> Array a
- stretchOuter :: HasCallStack => Int -> Array a -> Array a
- transpose :: HasCallStack => [Int] -> Array a -> Array a
- index :: (HasCallStack, Unbox a) => Array a -> Int -> Array a
- pad :: (HasCallStack, Unbox a) => [(Int, Int)] -> a -> Array a -> Array a
- mapA :: (Unbox a, Unbox b) => (a -> b) -> Array a -> Array b
- zipWithA :: (HasCallStack, Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Array a -> Array b -> Array c
- zipWith3A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Array a -> Array b -> Array c -> Array d
- zipWith4A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => (a -> b -> c -> d -> e) -> Array a -> Array b -> Array c -> Array d -> Array e
- zipWith5A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => (a -> b -> c -> d -> e -> f) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f
- append :: (HasCallStack, Unbox a) => Array a -> Array a -> Array a
- concatOuter :: (HasCallStack, Unbox a) => [Array a] -> Array a
- ravel :: (HasCallStack, Unbox a) => Array (Array a) -> Array a
- unravel :: (HasCallStack, Unbox a) => Array a -> Array (Array a)
- window :: HasCallStack => [Int] -> Array a -> Array a
- stride :: HasCallStack => [Int] -> Array a -> Array a
- rotate :: (HasCallStack, Unbox a) => Int -> Int -> Array a -> Array a
- slice :: HasCallStack => [(Int, Int)] -> Array a -> Array a
- rerank :: (HasCallStack, Unbox a, Unbox b) => Int -> (Array a -> Array b) -> Array a -> Array b
- rerank2 :: (HasCallStack, Unbox a, Unbox b, Unbox c) => Int -> (Array a -> Array b -> Array c) -> Array a -> Array b -> Array c
- rev :: [Int] -> Array a -> Array a
- reduce :: Unbox a => (a -> a -> a) -> a -> Array a -> Array a
- foldrA :: Unbox a => (a -> b -> b) -> b -> Array a -> b
- traverseA :: (Unbox a, Unbox b, Applicative f) => (a -> f b) -> Array a -> f (Array b)
- allSameA :: (Unbox a, Eq a) => Array a -> Bool
- sumA :: (Unbox a, Num a) => Array a -> a
- productA :: (Unbox a, Num a) => Array a -> a
- maximumA :: (HasCallStack, Unbox a, Ord a) => Array a -> a
- minimumA :: (HasCallStack, Unbox a, Ord a) => Array a -> a
- anyA :: Unbox a => (a -> Bool) -> Array a -> Bool
- allA :: Unbox a => (a -> Bool) -> Array a -> Bool
- broadcast :: (HasCallStack, Unbox a) => [Int] -> ShapeL -> Array a -> Array a
- update :: (HasCallStack, Unbox a) => Array a -> [([Int], a)] -> Array a
- generate :: Unbox a => ShapeL -> ([Int] -> a) -> Array a
- iterateN :: Unbox a => Int -> (a -> a) -> a -> Array a
- iota :: (Unbox a, Enum a, Num a) => Int -> Array a
- bitcast :: forall a b. (HasCallStack, Unbox a, Unbox b) => Array a -> Array b
Documentation
Instances
Eq (Array Vector a) => Eq (Array a) Source # | |
(Data a, Storable a) => Data (Array a) Source # | |
Defined in Data.Array.Internal.DynamicS gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array a -> c (Array a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array a) # toConstr :: Array a -> Constr # dataTypeOf :: Array a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array a)) # gmapT :: (forall b. Data b => b -> b) -> Array a -> Array a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array a -> r # gmapQ :: (forall d. Data d => d -> u) -> Array a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Array a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array a -> m (Array a) # | |
Ord (Array Vector a) => Ord (Array a) Source # | |
Defined in Data.Array.Internal.DynamicS | |
(Read a, Unbox a) => Read (Array a) Source # | |
(Show a, Unbox a) => Show (Array a) Source # | |
Generic (Array a) Source # | |
(Arbitrary a, Unbox a) => Arbitrary (Array a) Source # | |
NFData a => NFData (Array a) Source # | |
Defined in Data.Array.Internal.DynamicS | |
(Pretty a, Storable a) => Pretty (Array a) Source # | |
Defined in Data.Array.Internal.DynamicS pPrintPrec :: PrettyLevel -> Rational -> Array a -> Doc # pPrintList :: PrettyLevel -> [Array a] -> Doc # | |
(a ~ b, Unbox a) => Convert (Array a) (Array b) Source # | |
(a ~ b, Unbox a) => Convert (Array a) (Array b) Source # | |
a ~ b => Convert (Array a) (Array Vector b) Source # | |
(a ~ b, Shape sh) => Convert (Array a) (Array sh b) Source # | |
(a ~ b, KnownNat n) => Convert (Array a) (Array n b) Source # | |
(a ~ b, Shape sh) => Convert (Array sh a) (Array b) Source # | |
type Rep (Array a) Source # | |
Defined in Data.Array.Internal.DynamicS |
The Vector
class is the interface to the underlying storage for the arrays.
The operations map straight to operations for Vector
.
vIndex, vLength, vToList, vFromList, vSingleton, vReplicate, vMap, vZipWith, vZipWith3, vZipWith4, vZipWith5, vAppend, vConcat, vFold, vSlice, vSum, vProduct, vMaximum, vMinimum, vUpdate, vGenerate, vAll, vAny
Instances
The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.
Memory addresses are represented as values of type
, for some
Ptr
aa
which is an instance of class Storable
. The type argument to
Ptr
helps provide some valuable type safety in FFI code (you can't
mix pointers of different types without an explicit cast), while
helping the Haskell type system figure out which marshalling method is
needed for a given pointer.
All marshalling between Haskell and a foreign language ultimately
boils down to translating Haskell data structures into the binary
representation of a corresponding data structure of the foreign
language and vice versa. To code this marshalling in Haskell, it is
necessary to manipulate primitive data types stored in unstructured
memory blocks. The class Storable
facilitates this manipulation on
all types for which it is instantiated, which are the standard basic
types of Haskell, the fixed size Int
types (Int8
, Int16
,
Int32
, Int64
), the fixed size Word
types (Word8
, Word16
,
Word32
, Word64
), StablePtr
, all types from Foreign.C.Types,
as well as Ptr
.
sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)
Instances
shapeL :: Array a -> ShapeL Source #
The shape of an array, i.e., a list of the sizes of its dimensions. In the linearization of the array the outermost (i.e. first list element) varies most slowly. O(1) time.
rank :: Array a -> Int Source #
The rank of an array, i.e., the number if dimensions it has. O(1) time.
toList :: (HasCallStack, Unbox a) => Array a -> [a] Source #
Convert to a list with the elements in the linearization order. O(n) time.
fromList :: (HasCallStack, Unbox a) => ShapeL -> [a] -> Array a Source #
Convert from a list with the elements given in the linearization order. Fails if the given shape does not have the same number of elements as the list. O(n) time.
toVector :: (HasCallStack, Unbox a) => Array a -> Vector a Source #
Convert to a vector with the elements in the linearization order. O(n) or O(1) time (the latter if the vector is already in the linearization order).
fromVector :: (HasCallStack, Unbox a) => ShapeL -> Vector a -> Array a Source #
Convert from a vector with the elements given in the linearization order. Fails if the given shape does not have the same number of elements as the list. O(1) time.
normalize :: Unbox a => Array a -> Array a Source #
Make sure the underlying vector is in the linearization order. This is semantically an identity function, but can have big performance implications. O(n) or O(1) time.
unScalar :: (HasCallStack, Unbox a) => Array a -> a Source #
Convert a scalar (rank 0) array to a value. O(1) time.
constant :: Unbox a => ShapeL -> a -> Array a Source #
Make an array with all elements having the same value. O(1) time
reshape :: (HasCallStack, Unbox a) => ShapeL -> Array a -> Array a Source #
Change the shape of an array. Fails if the arrays have different number of elements. O(n) or O(1) time.
stretch :: HasCallStack => ShapeL -> Array a -> Array a Source #
Change the size of dimensions with size 1. These dimension can be changed to any size. All other dimensions must remain the same. O(1) time.
stretchOuter :: HasCallStack => Int -> Array a -> Array a Source #
Change the size of the outermost dimension by replication.
transpose :: HasCallStack => [Int] -> Array a -> Array a Source #
Do an arbitrary array transposition. Fails if the transposition argument is not a permutation of the numbers [0..r-1], where r is the rank of the array. O(1) time.
index :: (HasCallStack, Unbox a) => Array a -> Int -> Array a Source #
Index into an array. Fails if the array has rank 0 or if the index is out of bounds. O(1) time.
pad :: (HasCallStack, Unbox a) => [(Int, Int)] -> a -> Array a -> Array a Source #
Pad each dimension on the low and high side with the given value. O(n) time.
mapA :: (Unbox a, Unbox b) => (a -> b) -> Array a -> Array b Source #
Map over the array elements. O(n) time.
zipWithA :: (HasCallStack, Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Array a -> Array b -> Array c Source #
Map over the array elements. O(n) time.
zipWith3A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Array a -> Array b -> Array c -> Array d Source #
Map over the array elements. O(n) time.
zipWith4A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => (a -> b -> c -> d -> e) -> Array a -> Array b -> Array c -> Array d -> Array e Source #
Map over the array elements. O(n) time.
zipWith5A :: (HasCallStack, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => (a -> b -> c -> d -> e -> f) -> Array a -> Array b -> Array c -> Array d -> Array e -> Array f Source #
Map over the array elements. O(n) time.
append :: (HasCallStack, Unbox a) => Array a -> Array a -> Array a Source #
Append two arrays along the outermost dimension. All dimensions, except the outermost, must be the same. O(n) time.
concatOuter :: (HasCallStack, Unbox a) => [Array a] -> Array a Source #
Concatenate a number of arrays into a single array. Fails if any, but the outer, dimensions differ. O(n) time.
ravel :: (HasCallStack, Unbox a) => Array (Array a) -> Array a Source #
Turn a rank-1 array of arrays into a single array by making the outer array into the outermost dimension of the result array. All the arrays must have the same shape. O(n) time.
unravel :: (HasCallStack, Unbox a) => Array a -> Array (Array a) Source #
Turn an array into a nested array, this is the inverse of ravel
.
I.e., ravel . unravel == id
.
window :: HasCallStack => [Int] -> Array a -> Array a Source #
Make a window of the outermost dimensions.
The rank increases with the length of the window list.
E.g., if the shape of the array is [10,12,8]
and
the window size is [3,3]
then the resulting array will have shape
[8,10,3,3,8]
.
O(1) time.
stride :: HasCallStack => [Int] -> Array a -> Array a Source #
Stride the outermost dimensions.
E.g., if the array shape is [10,12,8]
and the strides are
[2,2]
then the resulting shape will be [5,6,8]
.
O(1) time.
rotate :: (HasCallStack, Unbox a) => Int -> Int -> Array a -> Array a Source #
Rotate the array k times along the d'th dimension.
E.g., if the array shape is [2, 3, 2]
, d is 1, and k is 4,
the resulting shape will be [2, 4, 3, 2]
.
slice :: HasCallStack => [(Int, Int)] -> Array a -> Array a Source #
Extract a slice of an array.
The first argument is a list of (offset, length) pairs.
The length of the slicing argument must not exceed the rank of the arrar.
The extracted slice mul fall within the array dimensions.
E.g. slice [1,2] (fromList [4] [1,2,3,4]) == [2,3]
.
O(1) time.
rerank :: (HasCallStack, Unbox a, Unbox b) => Int -> (Array a -> Array b) -> Array a -> Array b Source #
Apply a function to the subarrays n levels down and make the results into an array with the same n outermost dimensions. The n must not exceed the rank of the array. O(n) time.
rerank2 :: (HasCallStack, Unbox a, Unbox b, Unbox c) => Int -> (Array a -> Array b -> Array c) -> Array a -> Array b -> Array c Source #
Apply a two-argument function to the subarrays n levels down and make the results into an array with the same n outermost dimensions. The n must not exceed the rank of the array. O(n) time.
rev :: [Int] -> Array a -> Array a Source #
Reverse the given dimensions, with the outermost being dimension 0. O(1) time.
foldrA :: Unbox a => (a -> b -> b) -> b -> Array a -> b Source #
Constrained version of foldr
for Arrays.
traverseA :: (Unbox a, Unbox b, Applicative f) => (a -> f b) -> Array a -> f (Array b) Source #
Constrained version of traverse
for Arrays.
allSameA :: (Unbox a, Eq a) => Array a -> Bool Source #
Check if all elements of the array are equal.
anyA :: Unbox a => (a -> Bool) -> Array a -> Bool Source #
Test if the predicate holds for any element.
allA :: Unbox a => (a -> Bool) -> Array a -> Bool Source #
Test if the predicate holds for all elements.
broadcast :: (HasCallStack, Unbox a) => [Int] -> ShapeL -> Array a -> Array a Source #
Put the dimensions of the argument into the specified dimensions, and just replicate the data along all other dimensions. The list of dimensions indicies must have the same rank as the argument array and it must be strictly ascending.
update :: (HasCallStack, Unbox a) => Array a -> [([Int], a)] -> Array a Source #
Update the array at the specified indicies to the associated value.
generate :: Unbox a => ShapeL -> ([Int] -> a) -> Array a Source #
Generate an array with a function that computes the value for each index.
bitcast :: forall a b. (HasCallStack, Unbox a, Unbox b) => Array a -> Array b Source #
Convert between types by just reinterpreting the bits as another type.
For instance the floating point number (1.5 :: Float)
will convert to
(0x3fc00000 :: Word32)
since they have the same bit representation.