orthotope-0.1.1.0: Multidimensional arrays inspired by APL
Safe HaskellNone
LanguageHaskell2010

Data.Array.ShapedG

Synopsis

Documentation

class Vector v Source #

The Vector class is the interface to the underlying storage for the arrays. The operations map straight to operations for Vector.

Associated Types

type VecElem v :: Type -> Constraint Source #

Instances

Instances details
Vector [] Source # 
Instance details

Defined in Data.Array.Internal

Associated Types

type VecElem [] :: Type -> Constraint Source #

Methods

vIndex :: VecElem [] a => [a] -> Int -> a Source #

vLength :: VecElem [] a => [a] -> Int Source #

vToList :: VecElem [] a => [a] -> [a] Source #

vFromList :: VecElem [] a => [a] -> [a] Source #

vSingleton :: VecElem [] a => a -> [a] Source #

vReplicate :: VecElem [] a => Int -> a -> [a] Source #

vMap :: (VecElem [] a, VecElem [] b) => (a -> b) -> [a] -> [b] Source #

vZipWith :: (VecElem [] a, VecElem [] b, VecElem [] c) => (a -> b -> c) -> [a] -> [b] -> [c] Source #

vZipWith3 :: (VecElem [] a, VecElem [] b, VecElem [] c, VecElem [] d) => (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] Source #

vZipWith4 :: (VecElem [] a, VecElem [] b, VecElem [] c, VecElem [] d, VecElem [] e) => (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e] Source #

vZipWith5 :: (VecElem [] a, VecElem [] b, VecElem [] c, VecElem [] d, VecElem [] e, VecElem [] f) => (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] Source #

vAppend :: VecElem [] a => [a] -> [a] -> [a] Source #

vConcat :: VecElem [] a => [[a]] -> [a] Source #

vFold :: VecElem [] a => (a -> a -> a) -> a -> [a] -> a Source #

vSlice :: VecElem [] a => Int -> Int -> [a] -> [a] Source #

vSum :: (VecElem [] a, Num a) => [a] -> a Source #

vProduct :: (VecElem [] a, Num a) => [a] -> a Source #

vMaximum :: (VecElem [] a, Ord a) => [a] -> a Source #

vMinimum :: (VecElem [] a, Ord a) => [a] -> a Source #

vUpdate :: VecElem [] a => [a] -> [(Int, a)] -> [a] Source #

vGenerate :: VecElem [] a => Int -> (Int -> a) -> [a] Source #

vAll :: VecElem [] a => (a -> Bool) -> [a] -> Bool Source #

vAny :: VecElem [] a => (a -> Bool) -> [a] -> Bool Source #

Vector Vector Source # 
Instance details

Defined in Data.Array.Internal.DynamicU

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

Vector Vector Source # 
Instance details

Defined in Data.Array.Internal.DynamicS

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

Vector Vector Source # 
Instance details

Defined in Data.Array.Internal.Dynamic

Associated Types

type VecElem Vector :: Type -> Constraint Source #

Methods

vIndex :: VecElem Vector a => Vector a -> Int -> a Source #

vLength :: VecElem Vector a => Vector a -> Int Source #

vToList :: VecElem Vector a => Vector a -> [a] Source #

vFromList :: VecElem Vector a => [a] -> Vector a Source #

vSingleton :: VecElem Vector a => a -> Vector a Source #

vReplicate :: VecElem Vector a => Int -> a -> Vector a Source #

vMap :: (VecElem Vector a, VecElem Vector b) => (a -> b) -> Vector a -> Vector b Source #

vZipWith :: (VecElem Vector a, VecElem Vector b, VecElem Vector c) => (a -> b -> c) -> Vector a -> Vector b -> Vector c Source #

vZipWith3 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d) => (a -> b -> c -> d) -> Vector a -> Vector b -> Vector c -> Vector d Source #

vZipWith4 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e) => (a -> b -> c -> d -> e) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e Source #

vZipWith5 :: (VecElem Vector a, VecElem Vector b, VecElem Vector c, VecElem Vector d, VecElem Vector e, VecElem Vector f) => (a -> b -> c -> d -> e -> f) -> Vector a -> Vector b -> Vector c -> Vector d -> Vector e -> Vector f Source #

vAppend :: VecElem Vector a => Vector a -> Vector a -> Vector a Source #

vConcat :: VecElem Vector a => [Vector a] -> Vector a Source #

vFold :: VecElem Vector a => (a -> a -> a) -> a -> Vector a -> a Source #

vSlice :: VecElem Vector a => Int -> Int -> Vector a -> Vector a Source #

vSum :: (VecElem Vector a, Num a) => Vector a -> a Source #

vProduct :: (VecElem Vector a, Num a) => Vector a -> a Source #

vMaximum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vMinimum :: (VecElem Vector a, Ord a) => Vector a -> a Source #

vUpdate :: VecElem Vector a => Vector a -> [(Int, a)] -> Vector a Source #

vGenerate :: VecElem Vector a => Int -> (Int -> a) -> Vector a Source #

vAll :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

vAny :: VecElem Vector a => (a -> Bool) -> Vector a -> Bool Source #

class Broadcast (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) Source #

Using the dimension indices ds, can sh be broadcast into shape sh'?

Minimal complete definition

broadcasting

Instances

Instances details
Broadcast' 0 ds sh sh' => Broadcast ds sh sh' Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Typeable s => Shape (s :: [Nat]) where Source #

Methods

shapeP :: Proxy s -> [Int] Source #

sizeP :: Proxy s -> Int Source #

Instances

Instances details
Shape ('[] :: [Nat]) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

shapeP :: Proxy '[] -> [Int] Source #

sizeP :: Proxy '[] -> Int Source #

(Shape s, KnownNat n) => Shape (n ': s) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

shapeP :: Proxy (n ': s) -> [Int] Source #

sizeP :: Proxy (n ': s) -> Int Source #

class Stride (ts :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ts ss -> rs Source #

Instances

Instances details
Stride ('[] :: [Nat]) ss ss Source # 
Instance details

Defined in Data.Array.Internal.Shape

(Stride ts ss rs, DivRoundUp s t ~ r) => Stride (t ': ts) (s ': ss) (r ': rs) Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Window (ws :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ws ss -> rs Source #

Instances

Instances details
Window' ws ws ss rs => Window ws ss rs Source # 
Instance details

Defined in Data.Array.Internal.Shape

class ValidDims (rs :: [Nat]) (sh :: [Nat]) Source #

Instances

Instances details
AllElem rs (Count 0 sh) => ValidDims rs sh Source # 
Instance details

Defined in Data.Array.Internal.Shape

type Permute (is :: [Nat]) (xs :: [Nat]) = Permute' is (Take (Rank is) xs) ++ Drop (Rank is) xs Source #

class Permutation (is :: [Nat]) Source #

Instances

Instances details
AllElem is (Count 0 is) => Permutation is Source # 
Instance details

Defined in Data.Array.Internal.Shape

type Size (s :: [Nat]) = Size' 1 s Source #

Compute the size, i.e., total number of elements of a type level shape.

type family Rank (s :: [Nat]) :: Nat where ... Source #

Compute the rank, i.e., length of a type level shape.

Equations

Rank '[] = 0 
Rank (n ': ns) = 1 + Rank ns 

data Array (sh :: [Nat]) v a Source #

Arrays stored in a v with values of type a.

Instances

Instances details
(a ~ b, s ~ t) => Convert (Array s a) (Array t Vector b) Source # 
Instance details

Defined in Data.Array.Convert

(a ~ b, s ~ t) => Convert (Array s a) (Array t Vector b) Source # 
Instance details

Defined in Data.Array.Convert

(a ~ b, s ~ t) => Convert (Array s a) (Array t Vector b) Source # 
Instance details

Defined in Data.Array.Convert

(Vector v, Eq a, VecElem v a, Eq (v a), Shape sh) => Eq (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

(==) :: Array sh v a -> Array sh v a -> Bool #

(/=) :: Array sh v a -> Array sh v a -> Bool #

(Typeable v, Typeable sh, Typeable a, Data (v a)) => Data (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Array sh v a -> c (Array sh v a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Array sh v a) #

toConstr :: Array sh v a -> Constr #

dataTypeOf :: Array sh v a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Array sh v a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Array sh v a)) #

gmapT :: (forall b. Data b => b -> b) -> Array sh v a -> Array sh v a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Array sh v a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Array sh v a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Array sh v a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Array sh v a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Array sh v a -> m (Array sh v a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Array sh v a -> m (Array sh v a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Array sh v a -> m (Array sh v a) #

(Vector v, Ord a, Ord (v a), VecElem v a, Shape sh) => Ord (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

compare :: Array sh v a -> Array sh v a -> Ordering #

(<) :: Array sh v a -> Array sh v a -> Bool #

(<=) :: Array sh v a -> Array sh v a -> Bool #

(>) :: Array sh v a -> Array sh v a -> Bool #

(>=) :: Array sh v a -> Array sh v a -> Bool #

max :: Array sh v a -> Array sh v a -> Array sh v a #

min :: Array sh v a -> Array sh v a -> Array sh v a #

(Shape sh, Vector v, Read a, VecElem v a) => Read (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

readsPrec :: Int -> ReadS (Array sh v a) #

readList :: ReadS [Array sh v a] #

readPrec :: ReadPrec (Array sh v a) #

readListPrec :: ReadPrec [Array sh v a] #

(Vector v, Show a, VecElem v a, Shape sh, Show (v a)) => Show (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

showsPrec :: Int -> Array sh v a -> ShowS #

show :: Array sh v a -> String #

showList :: [Array sh v a] -> ShowS #

Generic (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Associated Types

type Rep (Array sh v a) :: Type -> Type #

Methods

from :: Array sh v a -> Rep (Array sh v a) x #

to :: Rep (Array sh v a) x -> Array sh v a #

(Shape sh, Vector v, VecElem v a, Arbitrary a) => Arbitrary (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

arbitrary :: Gen (Array sh v a) #

shrink :: Array sh v a -> [Array sh v a] #

NFData (v a) => NFData (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

rnf :: Array sh v a -> () #

(Vector v, Pretty a, VecElem v a, Shape sh) => Pretty (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

Methods

pPrintPrec :: PrettyLevel -> Rational -> Array sh v a -> Doc #

pPrint :: Array sh v a -> Doc #

pPrintList :: PrettyLevel -> [Array sh v a] -> Doc #

type Rep (Array sh v a) Source # 
Instance details

Defined in Data.Array.Internal.ShapedG

type Rep (Array sh v a) = D1 ('MetaData "Array" "Data.Array.Internal.ShapedG" "orthotope-0.1.1.0-8N9XOymS4o4K1BvtpFJxFr" 'True) (C1 ('MetaCons "A" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (T v a))))

size :: forall sh v a. Shape sh => Array sh v a -> Int Source #

The number of elements in the array.

shapeL :: forall sh v a. Shape sh => Array sh v 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 :: forall sh v a. (Shape sh, KnownNat (Rank sh)) => Array sh v a -> Int Source #

The rank of an array, i.e., the number if dimensions it has. O(1) time.

index :: forall s sh v a. (HasCallStack, Vector v, KnownNat s) => Array (s ': sh) v a -> Int -> Array sh v a Source #

Index into an array. Fails if the array has rank 0 or if the index is out of bounds. O(1) time.

toList :: (Vector v, VecElem v a, Shape sh) => Array sh v a -> [a] Source #

Convert to a list with the elements in the linearization order. O(1) time.

toVector :: (Vector v, VecElem v a, Shape sh) => Array sh v a -> v 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).

fromList :: forall sh v a. (HasCallStack, Vector v, VecElem v a, Shape sh) => [a] -> Array sh v 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.

fromVector :: forall sh v a. (HasCallStack, Vector v, VecElem v a, Shape sh) => v a -> Array sh v 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 :: (Vector v, VecElem v a, Shape sh) => Array sh v a -> Array sh v 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.

reshape :: forall sh' sh v a. (Vector v, VecElem v a, Shape sh, Shape sh', Size sh ~ Size sh') => Array sh v a -> Array sh' v a Source #

Change the shape of an array. Type error if the arrays have different number of elements. O(n) or O(1) time.

stretch :: forall sh' sh v a. (Shape sh, Shape sh', ValidStretch sh sh') => Array sh v a -> Array sh' v 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 :: forall s sh v a. Shape sh => Array (1 ': sh) v a -> Array (s ': sh) v a Source #

Change the size of the outermost dimension by replication.

scalar :: (Vector v, VecElem v a) => a -> Array '[] v a Source #

Convert a value to a scalar (rank 0) array. O(1) time.

unScalar :: (Vector v, VecElem v a) => Array '[] v a -> a Source #

Convert a scalar (rank 0) array to a value. O(1) time.

constant :: forall sh v a. (Vector v, VecElem v a, Shape sh) => a -> Array sh v a Source #

Make an array with all elements having the same value. O(1) time.

mapA :: (Vector v, VecElem v a, VecElem v b, Shape sh) => (a -> b) -> Array sh v a -> Array sh v b Source #

Map over the array elements. O(n) time.

zipWithA :: (Vector v, VecElem v a, VecElem v b, VecElem v c, Shape sh) => (a -> b -> c) -> Array sh v a -> Array sh v b -> Array sh v c Source #

Map over the array elements. O(n) time.

zipWith3A :: (Vector v, VecElem v a, VecElem v b, VecElem v c, VecElem v d, Shape sh) => (a -> b -> c -> d) -> Array sh v a -> Array sh v b -> Array sh v c -> Array sh v d Source #

Map over the array elements. O(n) time.

pad :: forall ps sh' sh a v. (HasCallStack, Vector v, VecElem v a, Padded ps sh sh', Shape sh) => a -> Array sh v a -> Array sh' v a Source #

Pad each dimension on the low and high side with the given value. O(n) time.

transpose :: forall is sh v a. (Permutation is, Rank is <= Rank sh, Shape sh, Shape is, KnownNat (Rank sh)) => Array sh v a -> Array (Permute is sh) v 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.

append :: (Vector v, VecElem v a, Shape sh, KnownNat m, KnownNat n, KnownNat (m + n)) => Array (m ': sh) v a -> Array (n ': sh) v a -> Array ((m + n) ': sh) v a Source #

Append two arrays along the outermost dimension. All dimensions, except the outermost, must be the same. O(n) time.

ravel :: (Vector v, Vector v', VecElem v a, VecElem v' (Array sh v a), Shape sh, KnownNat s) => Array '[s] v' (Array sh v a) -> Array (s ': sh) v 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 :: (Vector v, Vector v', VecElem v a, VecElem v' (Array sh v a), Shape sh, KnownNat s) => Array (s ': sh) v a -> Array '[s] v' (Array sh v a) Source #

Turn an array into a nested array, this is the inverse of ravel. I.e., ravel . unravel == id. O(n) time.

window :: forall ws sh' sh v a. (Window ws sh sh', Vector v, KnownNat (Rank ws)) => Array sh v a -> Array sh' v 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].

E.g., window [2] (fromList [4] [1,2,3,4]) == fromList [3,2] [1,2, 2,3, 3,4] O(1) time.

If the window parameter ws = [w1,...,wk] and wa = window ws a then wa index i1 ... index ik == slice [(i1,w1),...,(ik,wk)] a.

stride :: forall ts sh' sh v a. (Stride ts sh sh', Vector v, Shape ts) => Array sh v a -> Array sh' v 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.

slice :: forall sl sh' sh v a. Slice sl sh sh' => Array sh v a -> Array sh' v a Source #

Extract a slice of an array. The first type argument is a list of (offset, length) pairs. The length of the slicing argument must not exceed the rank of the array. The extracted slice must fall within the array dimensions. E.g. slice '[ '(1,2)] (fromList '[4] [1,2,3,4]) == fromList '[2] [2,3]@. O(1) time.

rerank :: forall n i o sh v v' a b. (Vector v, Vector v', VecElem v a, VecElem v' b, Drop n sh ~ i, Shape sh, KnownNat n, Shape o, Shape (Take n sh ++ o)) => (Array i v a -> Array o v' b) -> Array sh v a -> Array (Take n sh ++ o) v' 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 :: forall n i1 i2 o sh1 sh2 r v a b c. (Vector v, VecElem v a, VecElem v b, VecElem v c, Drop n sh1 ~ i1, Drop n sh2 ~ i2, Shape sh1, Shape sh2, Take n sh1 ~ r, Take n sh2 ~ r, KnownNat n, Shape o, Shape (r ++ o)) => (Array i1 v a -> Array i2 v b -> Array o v c) -> Array sh1 v a -> Array sh2 v b -> Array (r ++ o) v 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 :: forall rs sh v a. (ValidDims rs sh, Shape rs, Shape sh) => Array sh v a -> Array sh v a Source #

Reverse the given dimensions, with the outermost being dimension 0. O(1) time.

reduce :: (Vector v, VecElem v a, Shape sh) => (a -> a -> a) -> a -> Array sh v a -> Array '[] v a Source #

Reduce all elements of an array into a rank 0 array. To reduce parts use rerank and transpose together with reduce. O(n) time.

foldrA :: (Vector v, VecElem v a, Shape sh) => (a -> b -> b) -> b -> Array sh v a -> b Source #

Right fold across all elements of an array.

traverseA :: (Vector v, VecElem v a, VecElem v b, Applicative f, Shape sh) => (a -> f b) -> Array sh v a -> f (Array sh v b) Source #

Constrained version of traverse for Arrays.

allSameA :: (Shape sh, Vector v, VecElem v a, Eq a) => Array sh v a -> Bool Source #

Check if all elements of the array are equal.

sumA :: (Vector v, VecElem v a, Num a, Shape sh) => Array sh v a -> a Source #

Sum of all elements.

productA :: (Vector v, VecElem v a, Num a, Shape sh) => Array sh v a -> a Source #

Product of all elements.

maximumA :: (Vector v, VecElem v a, Ord a, Shape sh, 1 <= Size sh) => Array sh v a -> a Source #

Maximum of all elements.

minimumA :: (Vector v, VecElem v a, Ord a, Shape sh, 1 <= Size sh) => Array sh v a -> a Source #

Minimum of all elements.

anyA :: (Vector v, VecElem v a, Shape sh) => (a -> Bool) -> Array sh v a -> Bool Source #

Test if the predicate holds for any element.

allA :: (Vector v, VecElem v a, Shape sh) => (a -> Bool) -> Array sh v a -> Bool Source #

Test if the predicate holds for all elements.

broadcast :: forall ds sh' sh v a. (Shape sh, Shape sh', Broadcast ds sh sh', Vector v, VecElem v a) => Array sh v a -> Array sh' v 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.

generate :: forall sh v a. (Vector v, VecElem v a, Shape sh) => ([Int] -> a) -> Array sh v a Source #

Generate an array with a function that computes the value for each index.

iterateN :: forall n v a. (Vector v, VecElem v a, KnownNat n) => (a -> a) -> a -> Array '[n] v a Source #

Iterate a function n times.

iota :: forall n v a. (Vector v, VecElem v a, KnownNat n, Enum a, Num a) => Array '[n] v a Source #

Generate a vector from 0 to n-1.