numhask-array-0.4.0.0: n-dimensional arrays

Safe HaskellNone
LanguageHaskell2010

NumHask.Array.Dynamic

Contents

Description

Arrays with a dynamic shape

Synopsis

Dynamic Arrays

data Array a Source #

a multidimensional array with a value-level shape

>>> 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
Functor Array Source # 
Instance details

Defined in NumHask.Array.Dynamic

Methods

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

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

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 #

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) #

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 #

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 #

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 #

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

Defined in NumHask.Array.Dynamic

Methods

rnf :: 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.4.0.0-LdEWQ1A9tQ8CbmYBdHSCA" 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))))

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

convert from a list

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

Operators

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

diag :: Array a -> Array a Source #

extract the diagonal

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

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

selects ds ps a select from a, elements along ds dimensions at positions ps

>>> 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 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]]

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 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 d i insert along the dimension d at position i

>>> 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 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]]

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 another binary other than addition

>>> 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.

dot sum (*) on two matrices is known as matrix multiplication

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

dot sum (*) on two vectors is known as the inner product

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

dot sum (*) m v on a matrix and a vector is 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]

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

select elements along 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 singleton dimensions

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

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

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

ident :: Num a => [Int] -> Array a Source #

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

Scalar

fromScalar :: Array a -> a Source #

Wiki Scalar

An Array with shape [] despite being a Scalar is nevertheless a one-element vector under the hood.

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 :: Num 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]]