numhask-array-0.11.0.1: Multi-dimensional arrays.
Safe HaskellSafe-Inferred
LanguageGHC2021

NumHask.Array.Dynamic

Description

Arrays with a dynamic shape (shape only known at runtime).

Synopsis

Documentation

>>> :set -XDataKinds
>>> :set -XOverloadedLists
>>> :set -XTypeFamilies
>>> :set -XFlexibleContexts
>>> :set -XRebindableSyntax
>>> import NumHask.Prelude
>>> import NumHask.Array.Dynamic
>>> import NumHask.Array.Shape
>>> let s = fromFlatList [] [1] :: Array Int
>>> let a = fromFlatList [2,3,4] [1..24] :: Array Int
>>> let v = fromFlatList [3] [1,2,3] :: Array Int
>>> let m = fromFlatList [3,4] [0..11] :: Array Int

data Array a Source #

a multidimensional array with a value-level shape

>>> let a = fromFlatList [2,3,4] [1..24] :: Array Int
>>> a
[[[1, 2, 3, 4],
  [5, 6, 7, 8],
  [9, 10, 11, 12]],
 [[13, 14, 15, 16],
  [17, 18, 19, 20],
  [21, 22, 23, 24]]]

Constructors

Array 

Fields

Instances

Instances details
Foldable Array Source # 
Instance details

Defined in NumHask.Array.Dynamic

Methods

fold :: Monoid m => Array m -> m #

foldMap :: Monoid m => (a -> m) -> Array a -> m #

foldMap' :: Monoid m => (a -> m) -> Array a -> m #

foldr :: (a -> b -> b) -> b -> Array a -> b #

foldr' :: (a -> b -> b) -> b -> Array a -> b #

foldl :: (b -> a -> b) -> b -> Array a -> b #

foldl' :: (b -> a -> b) -> b -> Array a -> b #

foldr1 :: (a -> a -> a) -> Array a -> a #

foldl1 :: (a -> a -> a) -> Array a -> a #

toList :: Array a -> [a] #

null :: Array a -> Bool #

length :: Array a -> Int #

elem :: Eq a => a -> Array a -> Bool #

maximum :: Ord a => Array a -> a #

minimum :: Ord a => Array a -> a #

sum :: Num a => Array a -> a #

product :: Num a => Array a -> a #

Traversable Array Source # 
Instance details

Defined in NumHask.Array.Dynamic

Methods

traverse :: Applicative f => (a -> f b) -> Array a -> f (Array b) #

sequenceA :: Applicative f => Array (f a) -> f (Array a) #

mapM :: Monad m => (a -> m b) -> Array a -> m (Array b) #

sequence :: Monad m => Array (m a) -> m (Array a) #

Functor Array Source # 
Instance details

Defined in NumHask.Array.Dynamic

Methods

fmap :: (a -> b) -> Array a -> Array b #

(<$) :: a -> Array b -> Array a #

Generic (Array a) Source # 
Instance details

Defined in NumHask.Array.Dynamic

Associated Types

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

Methods

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

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

Show a => Show (Array a) Source # 
Instance details

Defined in NumHask.Array.Dynamic

Methods

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

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Eq a => Eq (Array a) Source # 
Instance details

Defined in NumHask.Array.Dynamic

Methods

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

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

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

Defined in NumHask.Array.Dynamic

Methods

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

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

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

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

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

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

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

type Rep (Array a) Source # 
Instance details

Defined in NumHask.Array.Dynamic

type Rep (Array a) = D1 ('MetaData "Array" "NumHask.Array.Dynamic" "numhask-array-0.11.0.1-9YMpczlHMpNFmXfCLzzFiC" 'False) (C1 ('MetaCons "Array" 'PrefixI 'True) (S1 ('MetaSel ('Just "shape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: S1 ('MetaSel ('Just "unArray") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector a))))

Conversion

fromFlatList :: [Int] -> [a] -> Array a Source #

convert from a list

>>> fromFlatList [2,3,4] [1..24] == a
True

toFlatList :: Array a -> [a] Source #

convert to a flat list.

>>> toFlatList a == [1..24]
True

representable replacements

index :: Array a -> [Int] -> a Source #

extract an element at index i

>>> index a [1,2,3]
24

tabulate :: [Int] -> ([Int] -> a) -> Array a Source #

tabulate an array with a generating function

>>> tabulate [2,3,4] ((1+) . flatten [2,3,4]) == a
True

Operators

takes :: [Int] -> Array a -> Array a Source #

Takes the top-most elements according to the new dimension.

>>> takes [2,2,3] a
[[[1, 2, 3],
  [5, 6, 7]],
 [[13, 14, 15],
  [17, 18, 19]]]

reshape :: [Int] -> Array a -> Array a Source #

Reshape an array (with the same number of elements).

>>> reshape [4,3,2] a
[[[1, 2],
  [3, 4],
  [5, 6]],
 [[7, 8],
  [9, 10],
  [11, 12]],
 [[13, 14],
  [15, 16],
  [17, 18]],
 [[19, 20],
  [21, 22],
  [23, 24]]]

transpose :: Array a -> Array a Source #

Reverse indices eg transposes the element Aijk to Akji.

>>> index (transpose a) [1,0,0] == index a [0,0,1]
True

indices :: [Int] -> Array [Int] Source #

Indices of an Array.

>>> indices [3,3]
[[[0,0], [0,1], [0,2]],
 [[1,0], [1,1], [1,2]],
 [[2,0], [2,1], [2,2]]]

ident :: (Additive a, Multiplicative a) => [Int] -> Array a Source #

The identity array.

>>> ident [3,2]
[[1, 0],
 [0, 1],
 [0, 0]]

sequent :: [Int] -> Array Int Source #

An array of sequential Ints

>>> sequent [3]
[0, 1, 2]
>>> sequent [3,3]
[[0, 0, 0],
 [0, 1, 0],
 [0, 0, 2]]

diag :: Array a -> Array a Source #

Extract the diagonal of an array.

>>> diag (ident [3,2])
[1, 1]

undiag :: Additive a => Int -> Array a -> Array a Source #

Expand the array to form a diagonal array

>>> undiag 2 (fromFlatList [2] [1,1])
[[1, 0],
 [0, 1]]

singleton :: [Int] -> a -> Array a Source #

Create an array composed of a single value.

>>> singleton [3,2] one
[[1, 1],
 [1, 1],
 [1, 1]]

selects :: [Int] -> [Int] -> Array a -> Array a Source #

Select an array along dimensions.

>>> let s = selects [0,1] [1,1] a
>>> s
[17, 18, 19, 20]

selectsExcept :: [Int] -> [Int] -> Array a -> Array a Source #

Select an index except along specified dimensions

>>> let s = selectsExcept [2] [1,1] a
>>> s
[17, 18, 19, 20]

folds :: (Array a -> b) -> [Int] -> Array a -> Array b Source #

Fold along specified dimensions.

>>> folds sum [1] a
[68, 100, 132]

extracts :: [Int] -> Array a -> Array (Array a) Source #

Extracts dimensions to an outer layer.

>>> let e = extracts [1,2] a
>>> shape <$> extracts [0] a
[[3,4], [3,4]]

extractsExcept :: [Int] -> Array a -> Array (Array a) Source #

Extracts except dimensions to an outer layer.

>>> let e = extractsExcept [1,2] a
>>> shape <$> extracts [0] a
[[3,4], [3,4]]

joins :: [Int] -> Array (Array a) -> Array a Source #

Join inner and outer dimension layers.

>>> let e = extracts [1,0] a
>>> let j = joins [1,0] e
>>> a == j
True

maps :: (Array a -> Array b) -> [Int] -> Array a -> Array b Source #

Maps a function along specified dimensions.

>>> shape $ maps (transpose) [1] a
[4,3,2]

concatenate :: Int -> Array a -> Array a -> Array a Source #

Concatenate along a dimension.

>>> shape $ concatenate 1 a a
[2,6,4]

insert :: Int -> Int -> Array a -> Array a -> Array a Source #

Insert along a dimension at a position.

>>> insert 2 0 a (fromFlatList [2,3] [100..105])
[[[100, 1, 2, 3, 4],
  [101, 5, 6, 7, 8],
  [102, 9, 10, 11, 12]],
 [[103, 13, 14, 15, 16],
  [104, 17, 18, 19, 20],
  [105, 21, 22, 23, 24]]]

append :: Int -> Array a -> Array a -> Array a Source #

Insert along a dimension at the end.

>>> append 2 a (fromFlatList [2,3] [100..105])
[[[1, 2, 3, 4, 100],
  [5, 6, 7, 8, 101],
  [9, 10, 11, 12, 102]],
 [[13, 14, 15, 16, 103],
  [17, 18, 19, 20, 104],
  [21, 22, 23, 24, 105]]]

reorder :: [Int] -> Array a -> Array a Source #

change the order of dimensions

>>> let r = reorder [2,0,1] a
>>> r
[[[1, 5, 9],
  [13, 17, 21]],
 [[2, 6, 10],
  [14, 18, 22]],
 [[3, 7, 11],
  [15, 19, 23]],
 [[4, 8, 12],
  [16, 20, 24]]]

expand :: (a -> b -> c) -> Array a -> Array b -> Array c Source #

Product two arrays using the supplied binary function.

For context, if the function is multiply, and the arrays are tensors, then this can be interpreted as a tensor product.

https://en.wikipedia.org/wiki/Tensor_product

The concept of a tensor product is a dense crossroad, and a complete treatment is elsewhere. To quote: ... the tensor product can be extended to other categories of mathematical objects in addition to vector spaces, such as to matrices, tensors, algebras, topological vector spaces, and modules. In each such case the tensor product is characterized by a similar universal property: it is the freest bilinear operation. The general concept of a "tensor product" is captured by monoidal categories; that is, the class of all things that have a tensor product is a monoidal category.

>>> expand (*) v v
[[1, 2, 3],
 [2, 4, 6],
 [3, 6, 9]]

Alternatively, expand can be understood as representing the permutation of element pairs of two arrays, so like the Applicative List instance.

>>> i2 = indices [2,2]
>>> expand (,) i2 i2
[[[[([0,0],[0,0]), ([0,0],[0,1])],
   [([0,0],[1,0]), ([0,0],[1,1])]],
  [[([0,1],[0,0]), ([0,1],[0,1])],
   [([0,1],[1,0]), ([0,1],[1,1])]]],
 [[[([1,0],[0,0]), ([1,0],[0,1])],
   [([1,0],[1,0]), ([1,0],[1,1])]],
  [[([1,1],[0,0]), ([1,1],[0,1])],
   [([1,1],[1,0]), ([1,1],[1,1])]]]]

expandr :: (a -> b -> c) -> Array a -> Array b -> Array c Source #

Like expand, but permutes the first array first, rather than the second.

>>> expand (,) v (fmap (+3) v)
[[(1,4), (1,5), (1,6)],
 [(2,4), (2,5), (2,6)],
 [(3,4), (3,5), (3,6)]]
>>> expandr (,) v (fmap (+3) v)
[[(1,4), (2,4), (3,4)],
 [(1,5), (2,5), (3,5)],
 [(1,6), (2,6), (3,6)]]

apply :: Array (a -> b) -> Array a -> Array b Source #

Apply an array of functions to each array of values.

This is in the spirit of the applicative functor operation (<*>).

expand f a b == apply (fmap f a) b
>>> apply ((*) <$> v) v
[[1, 2, 3],
 [2, 4, 6],
 [3, 6, 9]]

Dynamic arrays can't be Applicatives because there is no pure (Shape is not known at compile-time).

>>> let b = fromFlatList [2,3] [1..6] :: Array Int
>>> contract sum [1,2] (apply (fmap (*) b) (transpose b))
[[14, 32],
 [32, 77]]

contract :: (Array a -> b) -> [Int] -> Array a -> Array b Source #

Contract an array by applying the supplied (folding) function on diagonal elements of the dimensions.

This generalises a tensor contraction by allowing the number of contracting diagonals to be other than 2, and allowing a binary operator other than multiplication.

>>> let b = fromFlatList [2,3] [1..6] :: Array Int
>>> contract sum [1,2] (expand (*) b (transpose b))
[[14, 32],
 [32, 77]]

dot :: (Array c -> d) -> (a -> b -> c) -> Array a -> Array b -> Array d Source #

A generalisation of a dot operation, which is a multiplicative expansion of two arrays and sum contraction along the middle two dimensions.

matrix multiplication

>>> let b = fromFlatList [2,3] [1..6] :: Array Int
>>> dot sum (*) b (transpose b)
[[14, 32],
 [32, 77]]

inner product

>>> let v = fromFlatList [3] [1..3] :: Array Int
>>> dot sum (*) v v
14

matrix-vector multiplication Note that an `Array Int` with shape [3] is neither a row vector nor column vector. dot is not turning the vector into a matrix and then using matrix multiplication.

>>> dot sum (*) v b
[9, 12, 15]
>>> dot sum (*) b v
[14, 32]

mult :: (Additive a, Multiplicative a) => Array a -> Array a -> Array a Source #

Array multiplication.

matrix multiplication

>>> let b = fromFlatList [2,3] [1..6] :: Array Int
>>> mult b (transpose b)
[[14, 32],
 [32, 77]]

inner product

>>> let v = fromFlatList [3] [1..3] :: Array Int
>>> mult v v
14

matrix-vector multiplication

>>> mult v b
[9, 12, 15]
>>> mult b v
[14, 32]

slice :: [[Int]] -> Array a -> Array a Source #

Select elements along positions in every dimension.

>>> let s = slice [[0,1],[0,2],[1,2]] a
>>> s
[[[2, 3],
  [10, 11]],
 [[14, 15],
  [22, 23]]]

squeeze :: Array a -> Array a Source #

Remove single dimensions.

>>> let a' = fromFlatList [2,1,3,4,1] [1..24] :: Array Int
>>> shape $ squeeze a'
[2,3,4]

Scalar

fromScalar :: Array a -> a Source #

Unwrapping scalars is probably a performance bottleneck.

>>> let s = fromFlatList [] [3] :: Array Int
>>> fromScalar s
3

toScalar :: a -> Array a Source #

Convert a number to a scalar.

>>> :t toScalar 2
toScalar 2 :: FromInteger a => Array a

Matrix

col :: Int -> Array a -> Array a Source #

extract specialised to a matrix

>>> col 1 m
[1, 5, 9]

row :: Int -> Array a -> Array a Source #

Extract specialised to a matrix.

>>> row 1 m
[4, 5, 6, 7]

mmult :: Ring a => Array a -> Array a -> Array a Source #

matrix multiplication

This is dot sum (*) specialised to matrices

>>> let a = fromFlatList [2,2] [1, 2, 3, 4] :: Array Int
>>> let b = fromFlatList [2,2] [5, 6, 7, 8] :: Array Int
>>> a
[[1, 2],
 [3, 4]]
>>> b
[[5, 6],
 [7, 8]]
>>> mmult a b
[[19, 22],
 [43, 50]]