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

Data.Array.RankedU

Synopsis

Documentation

type ShapeL = [Int] Source #

The shape of an array is a list of its dimensions.

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.

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 #

data Array n a Source #

Instances

Instances details
Eq (Array n Vector a) => Eq (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

(==) :: Array n a -> Array n a -> Bool #

(/=) :: Array n a -> Array n a -> Bool #

(KnownNat n, Data a, Unbox a) => Data (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

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

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

toConstr :: Array n a -> Constr #

dataTypeOf :: Array n a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord (Array n Vector a) => Ord (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

compare :: Array n a -> Array n a -> Ordering #

(<) :: Array n a -> Array n a -> Bool #

(<=) :: Array n a -> Array n a -> Bool #

(>) :: Array n a -> Array n a -> Bool #

(>=) :: Array n a -> Array n a -> Bool #

max :: Array n a -> Array n a -> Array n a #

min :: Array n a -> Array n a -> Array n a #

(KnownNat n, Read a, Unbox a) => Read (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

(Show a, Unbox a) => Show (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

showsPrec :: Int -> Array n a -> ShowS #

show :: Array n a -> String #

showList :: [Array n a] -> ShowS #

Generic (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Associated Types

type Rep (Array n a) :: Type -> Type #

Methods

from :: Array n a -> Rep (Array n a) x #

to :: Rep (Array n a) x -> Array n a #

(KnownNat r, Arbitrary a, Unbox a) => Arbitrary (Array r a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

arbitrary :: Gen (Array r a) #

shrink :: Array r a -> [Array r a] #

NFData a => NFData (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

rnf :: Array n a -> () #

(Pretty a, Unbox a) => Pretty (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

Methods

pPrintPrec :: PrettyLevel -> Rational -> Array n a -> Doc #

pPrint :: Array n a -> Doc #

pPrintList :: PrettyLevel -> [Array n a] -> Doc #

(a ~ b, n ~ m, Unbox a) => Convert (Array n a) (Array m b) Source # 
Instance details

Defined in Data.Array.Convert

Methods

convert :: Array0 n a -> Array m b Source #

convertE :: Array0 n a -> Either String (Array m b) Source #

(a ~ b, n ~ m, Unbox a) => Convert (Array n a) (Array m b) Source # 
Instance details

Defined in Data.Array.Convert

Methods

convert :: Array n a -> Array0 m b Source #

convertE :: Array n a -> Either String (Array0 m b) Source #

(a ~ b, n ~ m) => Convert (Array n a) (Array m Vector b) Source # 
Instance details

Defined in Data.Array.Convert

type Rep (Array n a) Source # 
Instance details

Defined in Data.Array.Internal.RankedU

type Rep (Array n a) = D1 ('MetaData "Array" "Data.Array.Internal.RankedU" "orthotope-0.1.2.0-CJAsudRdxTPDdvmYLqctaa" 'True) (C1 ('MetaCons "A" 'PrefixI 'True) (S1 ('MetaSel ('Just "unA") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Array n Vector a))))

size :: Array n a -> Int Source #

The number of elements in the array.

shapeL :: Array n 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 :: KnownNat n => Array n a -> Int Source #

The rank of an array, i.e., the number if dimensions it has, which is the n in Array n a. O(1) time.

index :: Unbox a => Array (1 + n) a -> Int -> Array n a Source #

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

toList :: Unbox a => Array n a -> [a] Source #

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

fromList :: (Unbox a, KnownNat n) => ShapeL -> [a] -> Array n 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 :: Unbox a => Array n 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 :: (Unbox a, KnownNat n) => ShapeL -> Vector a -> Array n 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, KnownNat n) => Array n a -> Array n 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 :: (Unbox a, KnownNat n, KnownNat n') => ShapeL -> Array n a -> Array n' a Source #

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

stretch :: ShapeL -> Array n a -> Array n 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, 1 <= n) => Int -> Array n a -> Array n a Source #

Change the size of the outermost dimension by replication.

scalar :: Unbox a => a -> Array 0 a Source #

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

unScalar :: Unbox a => Array 0 a -> a Source #

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

constant :: (Unbox a, KnownNat n) => ShapeL -> a -> Array n a Source #

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

mapA :: (Unbox a, Unbox b) => (a -> b) -> Array n a -> Array n b Source #

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

zipWithA :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Array n a -> Array n b -> Array n c Source #

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

zipWith3A :: (Unbox a, Unbox b, Unbox c, Unbox d) => (a -> b -> c -> d) -> Array n a -> Array n b -> Array n c -> Array n d Source #

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

pad :: (Unbox a, KnownNat n) => [(Int, Int)] -> a -> Array n a -> Array n a Source #

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

transpose :: KnownNat n => [Int] -> Array n a -> Array n 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 :: (Unbox a, KnownNat n) => Array n a -> Array n a -> Array n a Source #

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

concatOuter :: (Unbox a, KnownNat n) => [Array n a] -> Array n a Source #

Concatenate a number of arrays into a single array. Fails if any, but the outer, dimensions differ. O(n) time.

ravel :: (Unbox a, Unbox (Array n a), Unbox (Array n Vector a), KnownNat (1 + n)) => Array 1 (Array n a) -> Array (1 + n) 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 :: (Unbox a, Unbox (Array n a), Unbox (Array n Vector a)) => Array (1 + n) a -> Array 1 (Array n a) Source #

Turn an array into a nested array, this is the inverse of ravel. I.e., ravel . unravel == id.

window :: (KnownNat n, KnownNat n') => [Int] -> Array n a -> Array n' 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 :: [Int] -> Array n a -> Array n 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 :: forall d p a. (KnownNat p, KnownNat d, Unbox a, (d + (p + 1)) ~ ((p + d) + 1), (d + p) ~ (p + d), 1 <= (p + 1), KnownNat ((p + d) + 1), KnownNat (p + 1), KnownNat (1 + (p + 1))) => Int -> Array (p + d) a -> Array ((p + d) + 1) 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 :: [(Int, Int)] -> Array n a -> Array n 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 :: forall n i o a b. (Unbox a, Unbox b, KnownNat n, KnownNat o, KnownNat (n + o), KnownNat (1 + o)) => (Array i a -> Array o b) -> Array (n + i) a -> Array (n + o) 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(1) time.

rerank2 :: forall n i o a b c. (Unbox a, Unbox b, Unbox c, KnownNat n, KnownNat o, KnownNat (n + o), KnownNat (1 + o)) => (Array i a -> Array i b -> Array o c) -> Array (n + i) a -> Array (n + i) b -> Array (n + o) 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 n a -> Array n a Source #

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

reduce :: Unbox a => (a -> a -> a) -> a -> Array n a -> Array 0 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 :: Unbox a => (a -> b -> b) -> b -> Array n a -> b Source #

Constrained version of foldr for Arrays.

traverseA :: (Unbox a, Unbox b, Applicative f) => (a -> f b) -> Array n a -> f (Array n b) Source #

Constrained version of traverse for Arrays.

allSameA :: (Unbox a, Eq a) => Array n a -> Bool Source #

Check if all elements of the array are equal.

sumA :: (Unbox a, Num a) => Array r a -> a Source #

Sum of all elements.

productA :: (Unbox a, Num a) => Array r a -> a Source #

Product of all elements.

maximumA :: (Unbox a, Ord a) => Array r a -> a Source #

Maximum of all elements.

minimumA :: (Unbox a, Ord a) => Array r a -> a Source #

Minimum of all elements.

anyA :: Unbox a => (a -> Bool) -> Array r a -> Bool Source #

Test if the predicate holds for any element.

allA :: Unbox a => (a -> Bool) -> Array r a -> Bool Source #

Test if the predicate holds for all elements.

broadcast :: forall r' r a. (HasCallStack, Unbox a, KnownNat r, KnownNat r') => [Int] -> ShapeL -> Array r a -> Array r' 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 n a. (KnownNat n, Unbox a) => ShapeL -> ([Int] -> a) -> Array n a Source #

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

iterateN :: forall a. Unbox a => Int -> (a -> a) -> a -> Array 1 a Source #

Iterate a function n times.

iota :: (Unbox a, Enum a, Num a) => Int -> Array 1 a Source #

Generate a vector from 0 to n-1.