harpie-0.1.1.0: Haskell array programming.
Safe HaskellSafe-Inferred
LanguageGHC2021

Harpie.Fixed

Description

Arrays with shape information and computations at a type-level.

Synopsis

Usage

>>> :set -XDataKinds

Several names used in harpie conflict with Prelude:

>>> import Prelude hiding (cycle, repeat, take, drop, zipWith, length)

In general, Array functionality is contained in Harpie.Fixed and shape functionality is contained in Harpie.Shape. These two modules also have name clashes and at least one needs to be qualified:

>>> import Harpie.Fixed as F
>>> import Harpie.Shape qualified as S

prettyprinter is used to prettily render arrays to better visualise shape.

>>> import Prettyprinter hiding (dot,fill)

The Representable class from adjunctions is used heavily by the module.

>>> import Data.Functor.Rep

An important base accounting of Array shape is the singleton types SNat (a type-level Natural or Nat) from GHC.TypeNats in base. >>> import GHC.TypeNats

The (first-class-families)[https://hackage.haskell.org/package/first-class-families] library was used to code most of function constraints.

>>> import Fcf qualified

Examples of arrays:

An array with no dimensions (a scalar).

>>> s = 1 :: Array '[] Int
>>> s
[1]
>>> shape s
[]
>>> pretty s
1

A single-dimension array (a vector).

>>> let v = range @'[3]
>>> pretty v
[0,1,2]

A two-dimensional array (a matrix).

>>> let m = range @[2,3]
>>> pretty m
[[0,1,2],
 [3,4,5]]

An n-dimensional array (n should be finite).

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

Conversion to a dynamic, value-level shaped Array

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

Fixed Arrays

newtype Array (s :: [Nat]) a where Source #

A hyperrectangular (or multidimensional) array with a type-level shape.

>>> array @[2,3,4] @Int [1..24]
[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24]
>>> array [1..24] :: Array '[2,3,4] Int
[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24]
>>> pretty (array @[2,3,4] @Int [1..24])
[[[1,2,3,4],
  [5,6,7,8],
  [9,10,11,12]],
 [[13,14,15,16],
  [17,18,19,20],
  [21,22,23,24]]]
>>> array [1,2,3] :: Array '[2,2] Int
*** Exception: Shape Mismatch
...

In many situations, the use of TypeApplication can lead to a clean coding style.

>>> array @[2,3] @Int [1..6]
[1,2,3,4,5,6]

The main computational entry and exit points are often via index and tabulate with arrays indexed by Fins: >>> index a (S.UnsafeFins [1,2,3]) 23

>>> :t tabulate id :: Array [2,3] (Fins [2,3])
tabulate id :: Array [2,3] (Fins [2,3])
  :: Array [2, 3] (Fins [2, 3])
>>> pretty (tabulate id :: Array [2,3] (Fins [2,3]))
[[[0,0],[0,1],[0,2]],
 [[1,0],[1,1],[1,2]]]

Constructors

Array :: Vector a -> Array s a 

Instances

Instances details
KnownNats s => Representable (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Associated Types

type Rep (Array s) #

Methods

tabulate :: (Rep (Array s) -> a) -> Array s a #

index :: Array s a -> Rep (Array s) -> a #

Foldable (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

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

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

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

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

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

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

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

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

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

toList :: Array s a -> [a] #

null :: Array s a -> Bool #

length :: Array s a -> Int #

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

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

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

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

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

Eq1 (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

liftEq :: (a -> b -> Bool) -> Array s a -> Array s b -> Bool #

Ord1 (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

liftCompare :: (a -> b -> Ordering) -> Array s a -> Array s b -> Ordering #

Show1 (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Array s a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Array s a] -> ShowS #

Traversable (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

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

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

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

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

Functor (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

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

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

KnownNats s => Distributive (Array s) Source # 
Instance details

Defined in Harpie.Fixed

Methods

distribute :: Functor f => f (Array s a) -> Array s (f a) #

collect :: Functor f => (a -> Array s b) -> f a -> Array s (f b) #

distributeM :: Monad m => m (Array s a) -> Array s (m a) #

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

Generic (Array s a) Source # 
Instance details

Defined in Harpie.Fixed

Associated Types

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

Methods

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

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

(Num a, KnownNats s) => Num (Array s a) Source # 
Instance details

Defined in Harpie.Fixed

Methods

(+) :: Array s a -> Array s a -> Array s a #

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

(*) :: Array s a -> Array s a -> Array s a #

negate :: Array s a -> Array s a #

abs :: Array s a -> Array s a #

signum :: Array s a -> Array s a #

fromInteger :: Integer -> Array s a #

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

Defined in Harpie.Fixed

Methods

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

show :: Array s a -> String #

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

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

Defined in Harpie.Fixed

Methods

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

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

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

Defined in Harpie.Fixed

Methods

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

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

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

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

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

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

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

(KnownNats s, Show a) => Pretty (Array s a) Source # 
Instance details

Defined in Harpie.Fixed

Methods

pretty :: Array s a -> Doc ann #

prettyList :: [Array s a] -> Doc ann #

FromVector (Array s a) a Source # 
Instance details

Defined in Harpie.Fixed

Methods

asVector :: Array s a -> Vector a Source #

vectorAs :: Vector a -> Array s a Source #

type Rep (Array s) Source # 
Instance details

Defined in Harpie.Fixed

type Rep (Array s) = Fins s
type Rep (Array s a) Source # 
Instance details

Defined in Harpie.Fixed

type Rep (Array s a) = D1 ('MetaData "Array" "Harpie.Fixed" "harpie-0.1.1.0-Ve5Hc620vjHbkP6Ao490N" 'True) (C1 ('MetaCons "Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector a))))

unsafeArray :: (KnownNats s, FromVector t a) => t -> Array s a Source #

Construct an array without shape validation.

>>> unsafeArray [0..4] :: Array [2,3] Int
[0,1,2,3,4]

validate :: KnownNats s => Array s a -> Bool Source #

Validate the size and shape of an array.

>>> validate (unsafeArray [0..4] :: Array [2,3] Int)
False

safeArray :: (KnownNats s, FromVector t a) => t -> Maybe (Array s a) Source #

Construct an Array, checking shape.

>>> (safeArray [0..23] :: Maybe (Array [2,3,4] Int)) == Just a
True

array :: forall s a t. (KnownNats s, FromVector t a) => t -> Array s a Source #

Construct an Array, checking shape.

>>> array [0..22] :: Array [2,3,4] Int
*** Exception: Shape Mismatch
...

unsafeModifyShape :: forall s' s a. (KnownNats s, KnownNats s') => Array s a -> Array s' a Source #

Unsafely modify an array shape.

>>> pretty (unsafeModifyShape @[3,2] (array @[2,3] @Int [0..5]))
[[0,1],
 [2,3],
 [4,5]]

unsafeModifyVector :: KnownNats s => FromVector u a => FromVector v b => (u -> v) -> Array s a -> Array s b Source #

Unsafely modify an array vector.

>>> import Data.Vector qualified as V
>>> pretty (unsafeModifyVector (V.map (+1)) (array [0..5] :: Array [2,3] Int))
[[1,2,3],
 [4,5,6]]

Dimensions

type Dim = SNat Source #

Representation of an index into a shape (a type-level [Nat]). The index is a dimension of the shape.

pattern Dim :: () => KnownNat n => SNat n Source #

Pattern synonym for a Dim

type Dims = SNats Source #

Representation of indexes into a shape (a type-level [Nat]). The indexes are dimensions of the shape.

pattern Dims :: () => KnownNats ns => SNats ns Source #

Pattern synonym for a Dims

Conversion

class FromVector t a | t -> a where Source #

Conversion to and from a Vector

Note that conversion of an Array to a vector drops shape information, so that:

vectorAs . asVector == id
asVector . vectorAs == flat
>>> asVector (range @[2,3])
[0,1,2,3,4,5]
>>> import Data.Vector qualified as V
>>> vectorAs (V.fromList [0..5]) :: Array [2,3] Int
[0,1,2,3,4,5]

Methods

asVector :: t -> Vector a Source #

vectorAs :: Vector a -> t Source #

Instances

Instances details
FromVector (Vector a) a Source # 
Instance details

Defined in Harpie.Fixed

FromVector [a] a Source # 
Instance details

Defined in Harpie.Fixed

Methods

asVector :: [a] -> Vector a Source #

vectorAs :: Vector a -> [a] Source #

FromVector (Array s a) a Source # 
Instance details

Defined in Harpie.Fixed

Methods

asVector :: Array s a -> Vector a Source #

vectorAs :: Vector a -> Array s a Source #

toDynamic :: KnownNats s => Array s a -> Array a Source #

Convert to a dynamic array with shape at the value level.

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

with :: forall a r. Array a -> (forall s. KnownNats s => Array s a -> r) -> r Source #

Use a dynamic array in a fixed context.

>>> import qualified Harpie.Array as A
>>> with (A.range [2,3,4]) show
"[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23]"

This doesn't work for anything more complex where KnownNats need to be type computed:

>>> :t with (A.range [2,3,4]) (pretty . F.takes (Dims @'[0]) (S.SNats @'[1]))
...
    • Could not deduce ‘S.KnownNats (Fcf.Data.List.Drop_ 1 s)’
...

data SomeArray a Source #

Sigma type for an Array

A fixed Array where shape was unknown at runtime.

The library design encourages the use of value-level shape arrays (in Harpie.Array) via toDynamic in preference to dependent-type styles of coding. In particular, no attempt has been made to prove to the compiler that a particular Shape (resulting from any of the supplied functions) exists. Life is short.

P.take 4 <$> sample' arbitrary :: IO [SomeArray Int]
SomeArray SNats @'[
[0],SomeArray SNats '[0] [],SomeArray SNats [1, 1] [1],SomeArray SNats @[5, 1, 4] [2,1,0,2,-6,0,5,6,-1,-4,0,5,-1,6,4,-6,1,0,3,-1]]

Constructors

forall s. SomeArray (SNats s) (Array s a) 

Instances

Instances details
Foldable SomeArray Source # 
Instance details

Defined in Harpie.Fixed

Methods

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

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

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

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

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

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

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

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

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

toList :: SomeArray a -> [a] #

null :: SomeArray a -> Bool #

length :: SomeArray a -> Int #

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

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

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

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

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

Functor SomeArray Source # 
Instance details

Defined in Harpie.Fixed

Methods

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

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

Arbitrary a => Arbitrary (SomeArray a) Source # 
Instance details

Defined in Harpie.Fixed

Methods

arbitrary :: Gen (SomeArray a) #

shrink :: SomeArray a -> [SomeArray a] #

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

Defined in Harpie.Fixed

someArray :: forall s t a. FromVector t a => SNats s -> t -> SomeArray a Source #

Contruct a SomeArray

Shape Access

shape :: forall a s. KnownNats s => Array s a -> [Int] Source #

Get shape of an Array as a value.

>>> shape a
[2,3,4]

rank :: forall a s. KnownNats s => Array s a -> Int Source #

Get rank of an Array as a value.

>>> rank a
3

size :: forall a s. KnownNats s => Array s a -> Int Source #

Get size of an Array as a value.

>>> size a
24

length :: KnownNats s => Array s a -> Int Source #

Number of rows (first dimension size) in an Array. As a convention, a scalar value is still a single row.

>>> length a
2
>>> length (toScalar 0)
1

isNull :: KnownNats s => Array s a -> Bool Source #

Is the Array empty (has zero number of elements).

>>> isNull (array [] :: Array [2,0] ())
True
>>> isNull (array [4] :: Array '[] Int)
False

Indexing

index :: Representable f => f a -> Rep f -> a #

If no definition is provided, this will default to gindex.

unsafeIndex :: KnownNats s => Array s a -> [Int] -> a Source #

Extract an element at an index, unsafely.

>>> unsafeIndex a [1,2,3]
23

(!) :: KnownNats s => Array s a -> [Int] -> a infixl 9 Source #

Extract an element at an index, unsafely.

>>> a ! [1,2,3]
23

(!?) :: KnownNats s => Array s a -> [Int] -> Maybe a infixl 9 Source #

Extract an element at an index, safely.

>>> a !? [1,2,3]
Just 23
>>> a !? [2,3,1]
Nothing

tabulate :: Representable f => (Rep f -> a) -> f a #

fmap f . tabulatetabulate . fmap f

If no definition is provided, this will default to gtabulate.

unsafeTabulate :: KnownNats s => ([Int] -> a) -> Array s a Source #

Tabulate unsafely.

>>> :t tabulate @(Array [2,3]) id
tabulate @(Array [2,3]) id :: Array [2, 3] (Fins [2, 3])
>>> :t unsafeTabulate @[2,3] id
unsafeTabulate @[2,3] id :: Array [2, 3] [Int]
>>> pretty $ unsafeTabulate @[2,3] id
[[[0,0],[0,1],[0,2]],
 [[1,0],[1,1],[1,2]]]

backpermute :: forall s' s a. (KnownNats s, KnownNats s') => (Fins s' -> Fins s) -> Array s a -> Array s' a Source #

backpermute is a tabulation where the contents of an array do not need to be accessed, and is thus a fulcrum for leveraging laziness and fusion via the rule:

backpermute f (backpermute f' a) == backpermute (f . f') a

Many functions in this module are examples of backpermute usage.

>>> pretty $ backpermute @[4,3,2] (UnsafeFins . List.reverse . fromFins) a
[[[0,12],
  [4,16],
  [8,20]],
 [[1,13],
  [5,17],
  [9,21]],
 [[2,14],
  [6,18],
  [10,22]],
 [[3,15],
  [7,19],
  [11,23]]]

unsafeBackpermute :: forall s' s a. (KnownNats s, KnownNats s') => ([Int] -> [Int]) -> Array s a -> Array s' a Source #

Unsafe backpermute

>>> pretty $ unsafeBackpermute @[4,3,2] List.reverse a
[[[0,12],
  [4,16],
  [8,20]],
 [[1,13],
  [5,17],
  [9,21]],
 [[2,14],
  [6,18],
  [10,22]],
 [[3,15],
  [7,19],
  [11,23]]]

Scalars

fromScalar :: Array '[] a -> a Source #

Unwrap a scalar.

>>> s = array @'[] @Int [3]
>>> :t fromScalar s
fromScalar s :: Int

toScalar :: a -> Array '[] a Source #

Wrap a scalar.

>>> :t toScalar @Int 2
toScalar @Int 2 :: Array '[] Int

isScalar :: KnownNats s => Array s a -> Bool Source #

Is an array a scalar?

>>> isScalar (toScalar (2::Int))
True

asSingleton :: (KnownNats s, KnownNats s', s' ~ Eval (AsSingleton s)) => Array s a -> Array s' a Source #

Convert a scalar to being a dimensioned array. Do nothing if not a scalar.

>>> asSingleton (toScalar 4)
[4]

asScalar :: (KnownNats s, KnownNats s', s' ~ Eval (AsScalar s)) => Array s a -> Array s' a Source #

Convert an array with shape [1] to being a scalar (Do nothing if not a shape [1] array).

>>> pretty (asScalar (singleton 3))
3

Array Creation

empty :: Array '[0] a Source #

An array with no elements.

>>> toDynamic empty
UnsafeArray [0] []

range :: forall s. KnownNats s => Array s Int Source #

An enumeration of row-major or lexicographic order.

>>> pretty (range :: Array [2,3] Int)
[[0,1,2],
 [3,4,5]]

corange :: forall s. KnownNats s => Array s Int Source #

An enumeration of col-major or colexicographic order.

>>> pretty (corange @[2,3,4])
[[[0,6,12,18],
  [2,8,14,20],
  [4,10,16,22]],
 [[1,7,13,19],
  [3,9,15,21],
  [5,11,17,23]]]

indices :: KnownNats s => Array s [Int] Source #

Indices of an array shape.

>>> pretty $ indices @[3,3]
[[[0,0],[0,1],[0,2]],
 [[1,0],[1,1],[1,2]],
 [[2,0],[2,1],[2,2]]]

ident :: (KnownNats s, Num a) => Array s a Source #

The identity array.

>>> pretty $ ident @[3,3]
[[1,0,0],
 [0,1,0],
 [0,0,1]]

konst :: KnownNats s => a -> Array s a Source #

Create an array composed of a single value.

>>> pretty $ konst @[3,2] 1
[[1,1],
 [1,1],
 [1,1]]

singleton :: a -> Array '[1] a Source #

Create an array of shape [1].

>>> pretty $ singleton 1
[1]

diag :: forall s' a s. (KnownNats s, KnownNats s', s' ~ Eval (MinDim s)) => Array s a -> Array s' a Source #

Extract the diagonal of an array.

>>> pretty $ diag (ident @[3,3])
[1,1,1]

undiag :: forall s' a s. (KnownNats s, KnownNats s', s' ~ Eval ((++) s s), Num a) => Array s a -> Array s' a Source #

Expand an array to form a diagonal array

>>> pretty $ undiag (range @'[3])
[[0,0,0],
 [0,1,0],
 [0,0,2]]

Element-level functions

zipWith :: KnownNats s => (a -> b -> c) -> Array s a -> Array s b -> Array s c Source #

Zip two arrays at an element level.

>>> zipWith (-) v v
[0,0,0]

modify :: KnownNats s => Fins s -> (a -> a) -> Array s a -> Array s a Source #

Modify a single value at an index.

>>> pretty $ modify (S.UnsafeFins [0,0]) (const 100) (range @[3,2])
[[100,1],
 [2,3],
 [4,5]]

imap :: KnownNats s => ([Int] -> a -> b) -> Array s a -> Array s b Source #

Maps an index function at element-level.

>>> pretty $ imap (\xs x -> x - sum xs) a
[[[0,0,0,0],
  [3,3,3,3],
  [6,6,6,6]],
 [[11,11,11,11],
  [14,14,14,14],
  [17,17,17,17]]]

Function generalisers

rowWise :: forall a ds s s' xs proxy. (KnownNats s, KnownNats ds, ds ~ Eval (DimsOf xs)) => (Dims ds -> proxy xs -> Array s a -> Array s' a) -> proxy xs -> Array s a -> Array s' a Source #

With a function that takes dimensions and (type-level) parameters, apply the parameters to the initial dimensions. ie

rowWise f xs = f [0..rank xs - 1] xs
>>> toDynamic $ rowWise indexesT (S.SNats @[1,0]) a
UnsafeArray [4] [12,13,14,15]

colWise :: forall a ds s s' xs proxy. (KnownNats s, KnownNats ds, ds ~ Eval (EndDimsOf xs s)) => (Dims ds -> proxy xs -> Array s a -> Array s' a) -> proxy xs -> Array s a -> Array s' a Source #

With a function that takes dimensions and (type-level) parameters, apply the parameters to the the last dimensions. ie

colWise f xs = f (List.reverse [0 .. (rank a - 1)]) xs
>>> toDynamic $ colWise indexesT (S.SNats @[1,0]) a
UnsafeArray [2] [1,13]

Single-dimension functions

take :: forall d t s s' a. (KnownNats s, KnownNats s', s' ~ Eval (TakeDim d t s)) => Dim d -> SNat t -> Array s a -> Array s' a Source #

Take the top-most elements across the specified dimension.

>>> pretty $ take (Dim @2) (SNat @1) a
[[[0],
  [4],
  [8]],
 [[12],
  [16],
  [20]]]

takeB :: forall s s' a d t. (KnownNats s, KnownNats s', s' ~ Eval (TakeDim d t s)) => Dim d -> SNat t -> Array s a -> Array s' a Source #

Take the bottom-most elements across the specified dimension.

>>> pretty $ takeB (Dim @2) (SNat @1) a
[[[3],
  [7],
  [11]],
 [[15],
  [19],
  [23]]]

drop :: forall s s' a d t. (KnownNats s, KnownNats s', Eval (DropDim d t s) ~ s') => Dim d -> SNat t -> Array s a -> Array s' a Source #

Drop the top-most elements across the specified dimension.

>>> pretty $ drop (Dim @2) (SNat @1) a
[[[1,2,3],
  [5,6,7],
  [9,10,11]],
 [[13,14,15],
  [17,18,19],
  [21,22,23]]]

dropB :: forall s s' a d t. (KnownNats s, KnownNats s', Eval (DropDim d t s) ~ s') => Dim d -> SNat t -> Array s a -> Array s' a Source #

Drop the bottom-most elements across the specified dimension.

>>> pretty $ dropB (Dim @2) (SNat @1) a
[[[0,1,2],
  [4,5,6],
  [8,9,10]],
 [[12,13,14],
  [16,17,18],
  [20,21,22]]]

select :: forall d a p s s'. (KnownNats s, KnownNats s', s' ~ Eval (DeleteDim d s), p ~ Eval (GetDim d s)) => Dim d -> Fin p -> Array s a -> Array s' a Source #

Select an index along a dimension.

>>> let s = select (Dim @2) (S.fin @4 3) a
>>> pretty s
[[3,7,11],
 [15,19,23]]

insert :: forall s' s si d p a. (KnownNats s, KnownNats si, KnownNats s', s' ~ Eval (IncAt d s), p ~ Eval (GetDim d s), True ~ Eval (InsertOk d s si)) => Dim d -> Fin p -> Array s a -> Array si a -> Array s' a Source #

Insert along a dimension at a position.

>>> pretty $ insert (Dim @2) (UnsafeFin 0) a (konst @[2,3] 0)
[[[0,0,1,2,3],
  [0,4,5,6,7],
  [0,8,9,10,11]],
 [[0,12,13,14,15],
  [0,16,17,18,19],
  [0,20,21,22,23]]]
>>> toDynamic $ insert (Dim @0) (UnsafeFin 0) (toScalar 1) (toScalar 2)
UnsafeArray [2] [2,1]

delete :: forall d s s' p a. (KnownNats s, KnownNats s', s' ~ Eval (DecAt d s), p ~ (1 + Eval (GetDim d s))) => Dim d -> Fin p -> Array s a -> Array s' a Source #

Delete along a dimension at a position.

>>> pretty $ delete (Dim @2) (UnsafeFin 3) a
[[[0,1,2],
  [4,5,6],
  [8,9,10]],
 [[12,13,14],
  [16,17,18],
  [20,21,22]]]

append :: forall a d s si s'. (KnownNats s, KnownNats si, KnownNats s', s' ~ Eval (IncAt d s), True ~ Eval (InsertOk d s si)) => Dim d -> Array s a -> Array si a -> Array s' a Source #

Insert along a dimension at the end.

>>> pretty $ append (Dim @2) a (konst @[2,3] 0)
[[[0,1,2,3,0],
  [4,5,6,7,0],
  [8,9,10,11,0]],
 [[12,13,14,15,0],
  [16,17,18,19,0],
  [20,21,22,23,0]]]

prepend :: forall a d s si s'. (KnownNats s, KnownNats si, KnownNats s', s' ~ Eval (IncAt d s), True ~ Eval (InsertOk d s si)) => Dim d -> Array si a -> Array s a -> Array s' a Source #

Insert along a dimension at the beginning.

>>> pretty $ prepend (Dim @2) (konst @[2,3] 0) a
[[[0,0,1,2,3],
  [0,4,5,6,7],
  [0,8,9,10,11]],
 [[0,12,13,14,15],
  [0,16,17,18,19],
  [0,20,21,22,23]]]

concatenate :: forall a s0 s1 d s. (KnownNats s0, KnownNats s1, KnownNats s, Eval (Concatenate d s0 s1) ~ s) => Dim d -> Array s0 a -> Array s1 a -> Array s a Source #

Concatenate along a dimension.

>>> shape $ concatenate (Dim @1) a a
[2,6,4]
>>> toDynamic $ concatenate (Dim @0) (toScalar 1) (toScalar 2)
UnsafeArray [2] [1,2]
>>> toDynamic $ concatenate (Dim @0) (array @'[1] [0]) (array @'[3] [1..3])
UnsafeArray [4] [0,1,2,3]

couple :: forall d a s s' se. (KnownNat d, KnownNats s, KnownNats s', KnownNats se, s' ~ Eval (Concatenate d se se), se ~ Eval (InsertDim d 1 s)) => Dim d -> Array s a -> Array s a -> Array s' a Source #

Combine two arrays as a new dimension of a new array.

>>> pretty $ couple (Dim @0) (array @'[3] [1,2,3]) (array @'[3] @Int [4,5,6])
[[1,2,3],
 [4,5,6]]
>>> couple (Dim @0) (toScalar @Int 0) (toScalar 1)
[0,1]

slice :: forall a d off l s s'. (KnownNats s, KnownNats s', s' ~ Eval (SetDim d l s), Eval (SliceOk d off l s) ~ True) => Dim d -> SNat off -> SNat l -> Array s a -> Array s' a Source #

Slice along a dimension with the supplied offset & length.

>>> pretty $ slice (Dim @2) (SNat @1) (SNat @2) a
[[[1,2],
  [5,6],
  [9,10]],
 [[13,14],
  [17,18],
  [21,22]]]

rotate :: forall d s a. KnownNats s => Dim d -> Int -> Array s a -> Array s a Source #

Rotate an array along a dimension.

>>> pretty $ rotate (Dim @1) 2 a
[[[8,9,10,11],
  [0,1,2,3],
  [4,5,6,7]],
 [[20,21,22,23],
  [12,13,14,15],
  [16,17,18,19]]]

Multi-dimension functions

takes :: forall ds xs s' s a. (KnownNats s, KnownNats s', s' ~ Eval (SetDims ds xs s)) => Dims ds -> SNats xs -> Array s a -> Array s' a Source #

Across the specified dimensions, takes the top-most elements.

>>> pretty $ takes (Dims @[0,1]) (S.SNats @[1,2]) a
[[[0,1,2,3],
  [4,5,6,7]]]

takeBs :: forall s' s a ds xs. (KnownNats s, KnownNats s', KnownNats ds, KnownNats xs, s' ~ Eval (SetDims ds xs s)) => Dims ds -> SNats xs -> Array s a -> Array s' a Source #

Across the specified dimesnions, takes the bottom-most elements.

>>> pretty (takeBs (Dims @[0,1]) (S.SNats @[1,2]) a)
[[[16,17,18,19],
  [20,21,22,23]]]

drops :: forall ds xs s' s a. (KnownNats s, KnownNats s', KnownNats ds, KnownNats xs, s' ~ Eval (DropDims ds xs s)) => Dims ds -> SNats xs -> Array s a -> Array s' a Source #

Across the specified dimensions, drops the top-most elements.

>>> pretty $ drops (Dims @[0,2]) (S.SNats @[1,3]) a
[[[15],
  [19],
  [23]]]

dropBs :: forall s' s ds xs a. (KnownNats s, KnownNats s', KnownNats ds, KnownNats xs, s' ~ Eval (DropDims ds xs s)) => Dims ds -> SNats xs -> Array s a -> Array s' a Source #

Across the specified dimensions, drops the bottom-most elements.

>>> pretty $ dropBs (Dims @[0,2]) (S.SNats @[1,3]) a
[[[0],
  [4],
  [8]]]

indexes :: forall s' s ds xs a. (KnownNats s, KnownNats s', s' ~ Eval (DeleteDims ds s), xs ~ Eval (GetDims ds s)) => Dims ds -> Fins xs -> Array s a -> Array s' a Source #

Select by dimensions and indexes.

>>> pretty $ indexes (Dims @[0,1]) (S.UnsafeFins [1,1]) a
[16,17,18,19]

indexesT :: forall ds xs s s' a. (KnownNats s, KnownNats ds, KnownNats xs, KnownNats s', s' ~ Eval (DeleteDims ds s), True ~ Eval (IsFins xs =<< GetDims ds s)) => Dims ds -> SNats xs -> Array s a -> Array s' a Source #

Select by dimensions and indexes, supplying indexes as a type.

>>> pretty $ indexesT (Dims @[0,1]) (S.SNats @[1,1]) a
[16,17,18,19]

slices :: forall a ds ls offs s s'. (KnownNats s, KnownNats s', KnownNats ds, KnownNats ls, KnownNats offs, Eval (SlicesOk ds offs ls s) ~ True, Eval (SetDims ds ls s) ~ s') => Dims ds -> SNats offs -> SNats ls -> Array s a -> Array s' a Source #

Slice along dimensions with the supplied offsets and lengths.

>>> pretty $ slices (Dims @'[2]) (S.SNats @'[1]) (S.SNats @'[2]) a
[[[1,2],
  [5,6],
  [9,10]],
 [[13,14],
  [17,18],
  [21,22]]]

heads :: forall a ds s s'. (KnownNats s, KnownNats s', KnownNats ds, s' ~ Eval (DeleteDims ds s)) => Dims ds -> Array s a -> Array s' a Source #

Select the first element along the supplied dimensions.

>>> pretty $ heads (Dims @[0,2]) a
[0,4,8]

lasts :: forall ds s s' a. (KnownNats s, KnownNats ds, KnownNats s', s' ~ Eval (DeleteDims ds s)) => Dims ds -> Array s a -> Array s' a Source #

Select the last element along the supplied dimensions.

>>> pretty $ lasts (Dims @[0,2]) a
[15,19,23]

tails :: forall ds os s s' a ls. (KnownNats s, KnownNats ds, KnownNats s', KnownNats ls, KnownNats os, Eval (SlicesOk ds os ls s) ~ True, os ~ Eval (Replicate (Eval (Rank ds)) 1), ls ~ Eval (GetLastPositions ds s), s' ~ Eval (SetDims ds ls s)) => Dims ds -> Array s a -> Array s' a Source #

Select the tail elements along the supplied dimensions.

>>> pretty $ tails (Dims @[0,2]) a
[[[13,14,15],
  [17,18,19],
  [21,22,23]]]

inits :: forall ds os s s' a ls. (KnownNats s, KnownNats ds, KnownNats s', KnownNats ls, KnownNats os, Eval (SlicesOk ds os ls s) ~ True, os ~ Eval (Replicate (Eval (Rank ds)) 0), ls ~ Eval (GetLastPositions ds s), s' ~ Eval (SetDims ds ls s)) => Dims ds -> Array s a -> Array s' a Source #

Select the init elements along the supplied dimensions.

>>> pretty $ inits (Dims @[0,2]) a
[[[0,1,2],
  [4,5,6],
  [8,9,10]]]

Function application

extracts :: forall ds st si so a. (KnownNats st, KnownNats ds, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds st), so ~ Eval (GetDims ds st)) => Dims ds -> Array st a -> Array so (Array si a) Source #

Extracts specified dimensions to an outer layer.

>>> :t extracts (Dims @'[0]) (range @[2,3,4])
extracts (Dims @'[0]) (range @[2,3,4])
  :: Array '[2] (Array [3, 4] Int)

reduces :: forall ds st si so a b. (KnownNats st, KnownNats ds, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds st), so ~ Eval (GetDims ds st)) => Dims ds -> (Array si a -> b) -> Array st a -> Array so b Source #

Reduce along specified dimensions, using the supplied fold.

>>> pretty $ reduces (Dims @'[0]) sum a
[66,210]
>>> pretty $ reduces (Dims @[0,2]) sum a
[[12,15,18,21],
 [48,51,54,57]]

joins :: forall a ds si so st. (KnownNats ds, KnownNats st, KnownNats si, KnownNats so, Eval (InsertDims ds so si) ~ st) => Dims ds -> Array so (Array si a) -> Array st a Source #

Join inner and outer dimension layers by supplied dimensions.

>>> let e = extracts (Dims @[1,0]) a
>>> let j = joins (Dims @[1,0]) e
>>> a == j
True

join :: forall a si so st ds. (KnownNats st, KnownNats si, KnownNats so, KnownNats ds, ds ~ Eval (DimsOf so), st ~ Eval (InsertDims ds so si)) => Array so (Array si a) -> Array st a Source #

Join inner and outer dimension layers in outer dimension order.

>>> a == join (extracts (Dims @[0,1]) a)
True

traverses :: (Applicative f, KnownNats s, KnownNats si, KnownNats so, si ~ Eval (GetDims ds s), so ~ Eval (DeleteDims ds s), s ~ Eval (InsertDims ds si so)) => Dims ds -> (a -> f b) -> Array s a -> f (Array s b) Source #

Traverse along specified dimensions.

>>> traverses (Dims @'[1]) print (range @[2,3])
0
3
1
4
2
5
[(),(),(),(),(),()]

maps :: forall ds s s' si si' so a b. (KnownNats s, KnownNats s', KnownNats si, KnownNats si', KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s' ~ Eval (InsertDims ds so si'), s ~ Eval (InsertDims ds so si)) => Dims ds -> (Array si a -> Array si' b) -> Array s a -> Array s' b Source #

Maps a function along specified dimensions.

>>> pretty $ maps (Dims @'[1]) transpose a
[[[0,12],
  [4,16],
  [8,20]],
 [[1,13],
  [5,17],
  [9,21]],
 [[2,14],
  [6,18],
  [10,22]],
 [[3,15],
  [7,19],
  [11,23]]]

filters :: forall ds si so a. (KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds so), KnownNats (Eval (GetDims ds so))) => Dims ds -> (Array si a -> Bool) -> Array so a -> Array (Array si a) Source #

Filters along specified dimensions (which are flattened as a dynamic array).

>>> pretty $ filters (Dims @[0,1]) (any ((==0) . (`mod` 7))) a
[[0,1,2,3],[4,5,6,7],[12,13,14,15],[20,21,22,23]]

zips :: forall ds s s' si si' so a b c. (KnownNats s, KnownNats s', KnownNats si, KnownNats si', KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s' ~ Eval (InsertDims ds so si'), s ~ Eval (InsertDims ds so si)) => Dims ds -> (Array si a -> Array si b -> Array si' c) -> Array s a -> Array s b -> Array s' c Source #

Zips two arrays with a function along specified dimensions.

>>> pretty $ zips (Dims @[0,1]) (zipWith (,)) a (reverses (Dims @'[0]) a)
[[[(0,12),(1,13),(2,14),(3,15)],
  [(4,16),(5,17),(6,18),(7,19)],
  [(8,20),(9,21),(10,22),(11,23)]],
 [[(12,0),(13,1),(14,2),(15,3)],
  [(16,4),(17,5),(18,6),(19,7)],
  [(20,8),(21,9),(22,10),(23,11)]]]

modifies :: forall a si s ds so. (KnownNats s, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s ~ Eval (InsertDims ds so si)) => (Array si a -> Array si a) -> Dims ds -> Fins so -> Array s a -> Array s a Source #

Modify using the supplied function along dimensions and positions.

>>> pretty $ modifies (fmap (100+)) (Dims @'[2]) (S.UnsafeFins [0]) a
[[[100,1,2,3],
  [104,5,6,7],
  [108,9,10,11]],
 [[112,13,14,15],
  [116,17,18,19],
  [120,21,22,23]]]

diffs :: forall a b ds ls si si' st st' so postDrop. (KnownNats ls, KnownNats si, KnownNats si', KnownNats st, KnownNats st', KnownNats so, KnownNats postDrop, si ~ Eval (DeleteDims ds postDrop), so ~ Eval (GetDims ds postDrop), st' ~ Eval (InsertDims ds so si'), postDrop ~ Eval (InsertDims ds so si), postDrop ~ Eval (DropDims ds ls st)) => Dims ds -> SNats ls -> (Array si a -> Array si a -> Array si' b) -> Array st a -> Array st' b Source #

Apply a binary function between successive slices, across dimensions and lags.

>>> pretty $ diffs (Dims @'[1]) (S.SNats @'[1]) (zipWith (-)) a
[[[4,4,4,4],
  [4,4,4,4]],
 [[4,4,4,4],
  [4,4,4,4]]]

Array expansion & contraction

expand :: forall sc sa sb a b c. (KnownNats sa, KnownNats sb, KnownNats sc, sc ~ Eval ((++) sa sb)) => (a -> b -> c) -> Array sa a -> Array sb b -> Array sc 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. The concept of a tensor product is a dense crossroad, and a complete treatment is elsewhere. To quote the wiki article:

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

>>> x = array [1,2,3] :: Array '[3] Int
>>> pretty $ expand (*) x x
[[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]
>>> pretty $ 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])]]]]

coexpand :: forall sc sa sb a b c. (KnownNats sa, KnownNats sb, KnownNats sc, sc ~ Eval ((++) sa sb)) => (a -> b -> c) -> Array sa a -> Array sb b -> Array sc c Source #

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

>>> pretty $ expand (,) v (fmap (+3) v)
[[(0,3),(0,4),(0,5)],
 [(1,3),(1,4),(1,5)],
 [(2,3),(2,4),(2,5)]]
>>> pretty $ coexpand (,) v (fmap (+3) v)
[[(0,3),(1,3),(2,3)],
 [(0,4),(1,4),(2,4)],
 [(0,5),(1,5),(2,5)]]

contract :: forall a b s ss se s' ds ds'. (KnownNats se, se ~ Eval (DeleteDims ds' s), KnownNats ds', KnownNats s, KnownNats ss, KnownNats s', s' ~ Eval (GetDims ds' s), ss ~ Eval (MinDim se), ds' ~ Eval (ExceptDims ds s)) => Dims ds -> (Array ss a -> b) -> Array s a -> Array s' 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.

>>> pretty $ contract (Dims @[1,2]) sum (expand (*) m (transpose m))
[[5,14],
 [14,50]]

prod :: forall a b c d s0 s1 so0 so1 si st ds0 ds1. (KnownNats so0, KnownNats so1, KnownNats si, KnownNats s0, KnownNats s1, KnownNats st, KnownNats ds0, KnownNats ds1, so0 ~ Eval (DeleteDims ds0 s0), so1 ~ Eval (DeleteDims ds1 s1), si ~ Eval (GetDims ds0 s0), si ~ Eval (GetDims ds1 s1), st ~ Eval ((++) so0 so1)) => Dims ds0 -> Dims ds1 -> (Array si c -> d) -> (a -> b -> c) -> Array s0 a -> Array s1 b -> Array st d Source #

Expand two arrays and then contract the result using the supplied matching dimensions.

>>> pretty $ prod (Dims @'[1]) (Dims @'[0]) sum (*) (range @[2,3]) (range @[3,2])
[[10,13],
 [28,40]]

With full laziness, this computation would be equivalent to:

f . diag <$> extracts (Dims @ds') (expand g a b)

dot :: forall a b c d ds0 ds1 s0 s1 so0 so1 st si. (KnownNats s0, KnownNats s1, KnownNats ds0, KnownNats ds1, KnownNats so0, KnownNats so1, KnownNats st, KnownNats si, so0 ~ Eval (DeleteDims ds0 s0), so1 ~ Eval (DeleteDims ds1 s1), si ~ Eval (GetDims ds0 s0), si ~ Eval (GetDims ds1 s1), st ~ Eval ((++) so0 so1), ds0 ~ '[Eval ((-) (Eval (Rank s0)) 1)], ds1 ~ '[0]) => (Array si c -> d) -> (a -> b -> c) -> Array s0 a -> Array s1 b -> Array st 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

>>> pretty $ dot sum (*) m (transpose m)
[[5,14],
 [14,50]]

inner product

>>> pretty $ dot sum (*) v v
5

matrix-vector multiplication Note that an Array with shape [3] is neither a row vector nor column vector.

>>> pretty $ dot sum (*) v (transpose m)
[5,14]
>>> pretty $ dot sum (*) m v
[5,14]

mult :: forall a ds0 ds1 s0 s1 so0 so1 st si. (Num a, KnownNats s0, KnownNats s1, KnownNats ds0, KnownNats ds1, KnownNats so0, KnownNats so1, KnownNats st, KnownNats si, so0 ~ Eval (DeleteDims ds0 s0), so1 ~ Eval (DeleteDims ds1 s1), si ~ Eval (GetDims ds0 s0), si ~ Eval (GetDims ds1 s1), st ~ Eval ((++) so0 so1), ds0 ~ '[Eval ((-) (Eval (Rank s0)) 1)], ds1 ~ '[0]) => Array s0 a -> Array s1 a -> Array st a Source #

Array multiplication.

matrix multiplication

>>> pretty $ mult m (transpose m)
[[5,14],
 [14,50]]

inner product

>>> pretty $ mult v v
5

matrix-vector multiplication

>>> pretty $ mult v (transpose m)
[5,14]
>>> pretty $ mult m v
[5,14]

windows :: forall w s ws a. (KnownNats s, KnownNats ws, ws ~ Eval (ExpandWindows w s)) => SNats w -> Array s a -> Array ws a Source #

windows xs are xs-sized windows of an array

>>> shape $ windows (Dims @[2,2]) (range @[4,3,2])
[3,2,2,2,2]

Search

find :: forall s' si s a r i' re ws. (Eq a, KnownNats si, KnownNats s, KnownNats s', KnownNats re, KnownNats i', KnownNat r, KnownNats ws, ws ~ Eval (ExpandWindows i' s), r ~ Eval (Rank s), i' ~ Eval (Rerank r si), re ~ Eval (DimWindows ws s), i' ~ Eval (DeleteDims re ws), s' ~ Eval (GetDims re ws)) => Array si a -> Array s a -> Array s' Bool Source #

Find the starting positions of occurences of one array in another.

>>> a = cycle @[4,4] (range @'[3])
>>> i = array @[2,2] [1,2,2,0]
>>> pretty $ find i a
[[False,True,False],
 [True,False,False],
 [False,False,True]]

findNoOverlap :: forall s' si s a r i' re ws. (Eq a, KnownNats si, KnownNats s, KnownNats s', KnownNats re, KnownNats i', KnownNat r, KnownNats ws, ws ~ Eval (ExpandWindows i' s), r ~ Eval (Rank s), i' ~ Eval (Rerank r si), re ~ Eval (DimWindows ws s), i' ~ Eval (DeleteDims re ws), s' ~ Eval (GetDims re ws)) => Array si a -> Array s a -> Array s' Bool Source #

Find the ending positions of one array in another except where the array overlaps with another copy.

>>> a = konst @[5,5] @Int 1
>>> i = konst @[2,2] @Int 1
>>> pretty $ findNoOverlap i a
[[True,False,True,False],
 [False,False,False,False],
 [True,False,True,False],
 [False,False,False,False]]

isPrefixOf :: forall s' s r a. (Eq a, KnownNats s, KnownNats s', KnownNat r, KnownNats (Eval (Rerank r s)), True ~ Eval (IsSubset s' s), r ~ Eval (Rank s')) => Array s' a -> Array s a -> Bool Source #

Check if the first array is a prefix of the second.

>>> isPrefixOf (array @[2,2] [0,1,4,5]) a
True

isSuffixOf :: forall s' s r a. (Eq a, KnownNats s, KnownNats s', KnownNat r, KnownNats (Eval (Rerank r s)), r ~ Eval (Rank s'), True ~ Eval (IsSubset s' s)) => Array s' a -> Array s a -> Bool Source #

Check if the first array is a suffix of the second.

>>> isSuffixOf (array @[2,2] [18,19,22,23]) a
True

isInfixOf :: forall s' si s a r i' re ws. (Eq a, KnownNats si, KnownNats s, KnownNats s', KnownNats re, KnownNats i', KnownNat r, KnownNats ws, ws ~ Eval (ExpandWindows i' s), r ~ Eval (Rank s), i' ~ Eval (Rerank r si), re ~ Eval (DimWindows ws s), i' ~ Eval (DeleteDims re ws), s' ~ Eval (GetDims re ws)) => Array si a -> Array s a -> Bool Source #

Check if the first array is an infix of the second.

>>> isInfixOf (array @[2,2] [18,19,22,23]) a
True

Shape manipulations

fill :: forall s' a s. (KnownNats s, KnownNats s') => a -> Array s a -> Array s' a Source #

Fill an array with the supplied value without regard to the original shape or cut the array values to match array size.

validate (def x a) == True
>>> pretty $ fill @'[3] 0 (array @'[0] [])
[0,0,0]
>>> pretty $ fill @'[3] 0 (array @'[4] [1..4])
[1,2,3]

cut :: forall s' s r a. (KnownNats s, KnownNats s', KnownNat r, KnownNats (Eval (Rerank r s)), True ~ Eval (IsSubset s' s), r ~ Eval (Rank s')) => Array s a -> Array s' a Source #

Cut an array to form a new (smaller) shape. Errors if the new shape is larger. The old array is reranked to the rank of the new shape first.

>>> toDynamic $ cut @'[2] (array @'[4] @Int [0..3])
UnsafeArray [2] [0,1]

cutSuffix :: forall s' s a r. (KnownNats s, KnownNats s', KnownNat r, KnownNats (Eval (Rerank r s)), r ~ Eval (Rank s'), True ~ Eval (IsSubset s' s)) => Array s a -> Array s' a Source #

Cut an array to form a new (smaller) shape, using suffix elements. Errors if the new shape is larger. The old array is reranked to the rank of the new shape first.

>>> toDynamic $ cutSuffix @[2,2] a
UnsafeArray [2,2] [18,19,22,23]

pad :: forall s' a s r. (KnownNats s, KnownNats s', KnownNat r, KnownNats (Eval (Rerank r s)), r ~ Eval (Rank s')) => a -> Array s a -> Array s' a Source #

Pad an array to form a new shape, supplying a default value for elements outside the shape of the old array. The old array is reranked to the rank of the new shape first.

>>> toDynamic $ pad @'[5] 0 (array @'[4] @Int [0..3])
UnsafeArray [5] [0,1,2,3,0]

lpad :: forall s' a s r. (KnownNats s, KnownNats s', KnownNat r, KnownNats (Eval (Rerank r s)), r ~ Eval (Rank s')) => a -> Array s a -> Array s' a Source #

Left pad an array to form a new shape, supplying a default value for elements outside the shape of the old array.

>>> toDynamic $ lpad @'[5] 0 (array @'[4] [0..3])
UnsafeArray [5] [0,0,1,2,3]
>>> pretty $ lpad @[3,3] 0 (range @[2,2])
[[0,0,0],
 [0,0,1],
 [0,2,3]]

reshape :: forall s' s a. (Eval (Size s) ~ Eval (Size s'), KnownNats s, KnownNats s') => Array s a -> Array s' a Source #

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

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

flat :: forall s' s a. (KnownNats s, KnownNats s', s' ~ '[Eval (Size s)]) => Array s a -> Array s' a Source #

Make an Array single dimensional.

>>> pretty $ flat (range @[2,2])
[0,1,2,3]
>>> pretty (flat $ toScalar 0)
[0]

repeat :: forall s' s a. (KnownNats s, KnownNats s', Eval (IsPrefixOf s s') ~ True) => Array s a -> Array s' a Source #

Reshape an array, repeating the original array. The shape of the array should be a suffix of the new shape.

>>> pretty $ repeat @[2,2,2] (array @'[2] [1,2])
[[[1,2],
  [1,2]],
 [[1,2],
  [1,2]]]
repeat ds (toScalar x) == konst ds x

cycle :: forall s' s a. (KnownNats s, KnownNats s') => Array s a -> Array s' a Source #

Reshape an array, cycling through the elements without regard to the original shape.

>>> pretty $ cycle @[2,2,2] (array @'[3] [1,2,3])
[[[1,2],
  [3,1]],
 [[2,3],
  [1,2]]]

rerank :: forall r s s' a. (KnownNats s, KnownNats s', s' ~ Eval (Rerank r s)) => SNat r -> Array s a -> Array s' a Source #

Change rank by adding new dimensions at the front, if the new rank is greater, or combining dimensions (from left to right) into rows, if the new rank is lower.

>>> shape (rerank (SNat @4) a)
[1,2,3,4]
>>> shape (rerank (SNat @2) a)
[6,4]
flat == rerank 1

reorder :: forall ds s s' a. (KnownNats s, KnownNats s', s' ~ Eval (Reorder s ds)) => SNats ds -> Array s a -> Array s' a Source #

Change the order of dimensions.

>>> pretty $ reorder (Dims @[2,0,1]) a
[[[0,4,8],
  [12,16,20]],
 [[1,5,9],
  [13,17,21]],
 [[2,6,10],
  [14,18,22]],
 [[3,7,11],
  [15,19,23]]]

squeeze :: forall s t a. (KnownNats s, KnownNats t, t ~ Eval (Squeeze s)) => Array s a -> Array t a Source #

Remove single dimensions.

>>> let sq = array [1..24] :: Array '[2,1,3,4,1] Int
>>> shape $ squeeze sq
[2,3,4]
>>> shape $ squeeze (singleton 0)
[]

elongate :: (KnownNats s, KnownNats s', s' ~ Eval (InsertDim d 1 s)) => Dim d -> Array s a -> Array s' a Source #

Insert a single dimension at the supplied position.

>>> shape $ elongate (SNat @1) a
[2,1,3,4]
>>> toDynamic $ elongate (SNat @0) (toScalar 1)
UnsafeArray [1] [1]

transpose :: forall a s s'. (KnownNats s, KnownNats s', s' ~ Eval (Reverse s)) => Array s a -> Array s' a Source #

Reverse indices eg transposes the element Aijk to Akji.

>>> (transpose a) ! [1,0,0] == a ! [0,0,1]
True
>>> pretty $ transpose (array @[2,2,2] [1..8])
[[[1,5],
  [3,7]],
 [[2,6],
  [4,8]]]

inflate :: forall s' s d x a. (KnownNats s, KnownNats s', s' ~ Eval (InsertDim d x s)) => Dim d -> SNat x -> Array s a -> Array s' a Source #

Inflate (or replicate) an array by inserting a new dimension given a supplied dimension and size.

>>> pretty $ inflate (SNat @0) (SNat @2) (array @'[3] [0,1,2])
[[0,1,2],
 [0,1,2]]

intercalate :: forall d ds n n' s si st a. (KnownNats s, KnownNats si, KnownNats st, KnownNats ds, KnownNat n, KnownNat n', ds ~ '[d], si ~ Eval (DeleteDim d s), n ~ Eval (GetDim d s), n' ~ Eval ((-) (Eval ((+) n n)) 1), st ~ Eval (InsertDim d n' si)) => Dim d -> Array si a -> Array s a -> Array st a Source #

Intercalate an array along dimensions.

>>> pretty $ intercalate (SNat @2) (konst @[2,3] 0) a
[[[0,0,1,0,2,0,3],
  [4,0,5,0,6,0,7],
  [8,0,9,0,10,0,11]],
 [[12,0,13,0,14,0,15],
  [16,0,17,0,18,0,19],
  [20,0,21,0,22,0,23]]]

intersperse :: forall d ds n n' s si st a. (KnownNats s, KnownNats si, KnownNats st, KnownNats ds, KnownNat n, KnownNat n', ds ~ '[d], si ~ Eval (DeleteDim d s), n ~ Eval (GetDim d s), n' ~ ((n + n) - 1), st ~ Eval (InsertDim d n' si)) => Dim d -> a -> Array s a -> Array st a Source #

Intersperse an element along dimensions.

>>> pretty $ intersperse (SNat @2) 0 a
[[[0,0,1,0,2,0,3],
  [4,0,5,0,6,0,7],
  [8,0,9,0,10,0,11]],
 [[12,0,13,0,14,0,15],
  [16,0,17,0,18,0,19],
  [20,0,21,0,22,0,23]]]

concats :: forall s s' newd ds a. (KnownNats s, KnownNats s', s' ~ Eval (ConcatDims ds newd s)) => Dims ds -> SNat newd -> Array s a -> Array s' a Source #

Concatenate dimensions, creating a new dimension at the supplied postion.

>>> pretty $ concats (Dims @[0,1]) (SNat @1) a
[[0,4,8,12,16,20],
 [1,5,9,13,17,21],
 [2,6,10,14,18,22],
 [3,7,11,15,19,23]]

reverses :: forall ds s a. KnownNats s => Dims ds -> Array s a -> Array s a Source #

Reverses element order along specified dimensions.

>>> pretty $ reverses (Dims @[0,1]) a
[[[20,21,22,23],
  [16,17,18,19],
  [12,13,14,15]],
 [[8,9,10,11],
  [4,5,6,7],
  [0,1,2,3]]]

rotates :: forall a ds s. (KnownNats s, True ~ Eval (IsDims ds s)) => Dims ds -> [Int] -> Array s a -> Array s a Source #

Rotate an array by/along dimensions & offsets.

>>> pretty $ rotates (Dims @'[1]) [2] a
[[[8,9,10,11],
  [0,1,2,3],
  [4,5,6,7]],
 [[20,21,22,23],
  [12,13,14,15],
  [16,17,18,19]]]

Sorting

sorts :: forall ds s a si so. (Ord a, KnownNats s, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s ~ Eval (InsertDims ds so si)) => Dims ds -> Array s a -> Array s a Source #

Sort an array along the supplied dimensions.

>>> pretty $ sorts (Dims @'[0]) (array @[2,2] [2,3,1,4])
[[1,4],
 [2,3]]
>>> pretty $ sorts (Dims @'[1]) (array @[2,2] [2,3,1,4])
[[2,3],
 [1,4]]
>>> pretty $ sorts (Dims @[0,1]) (array @[2,2] [2,3,1,4])
[[1,2],
 [3,4]]

sortsBy :: forall ds s a b si so. (Ord b, KnownNats s, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s ~ Eval (InsertDims ds so si)) => Dims ds -> (Array si a -> Array si b) -> Array s a -> Array s a Source #

The indices into the array if it were sorted by a comparison function along the dimensions supplied.

>>> import Data.Ord (Down (..))
>>> toDynamic $ sortsBy (Dims @'[0]) (fmap Down) (array @[2,2] [2,3,1,4])
UnsafeArray [2,2] [2,3,1,4]

orders :: forall ds s a si so. (Ord a, KnownNats s, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s ~ Eval (InsertDims ds so si)) => Dims ds -> Array s a -> Array so Int Source #

The indices into the array if it were sorted along the dimensions supplied.

>>> orders (Dims @'[0]) (array @[2,2] [2,3,1,4])
[1,0]

ordersBy :: forall ds s a b si so. (Ord b, KnownNats s, KnownNats si, KnownNats so, si ~ Eval (DeleteDims ds s), so ~ Eval (GetDims ds s), s ~ Eval (InsertDims ds so si)) => Dims ds -> (Array si a -> Array si b) -> Array s a -> Array so Int Source #

The indices into the array if it were sorted by a comparison function along the dimensions supplied.

>>> import Data.Ord (Down (..))
>>> ordersBy (Dims @'[0]) (fmap Down) (array @[2,2] [2,3,1,4])
[0,1]

Transmission

telecasts :: forall sa sb sc sia sib sic ma mb a b c soa sob ds. (KnownNats sa, KnownNats sb, KnownNats sc, KnownNats sia, KnownNats sib, KnownNats sic, KnownNats soa, KnownNats sob, KnownNats ds, ds ~ Eval (DimsOf soa), sia ~ Eval (DeleteDims ma sa), sib ~ Eval (DeleteDims mb sb), soa ~ Eval (GetDims ma sa), sob ~ Eval (GetDims mb sb), soa ~ sob, sc ~ Eval (InsertDims ds soa sic)) => SNats ma -> SNats mb -> (Array sia a -> Array sib b -> Array sic c) -> Array sa a -> Array sb b -> Array sc c Source #

Apply a binary array function to two arrays with matching shapes across the supplied (matching) dimensions.

>>> a = array @[2,3] [0..5]
>>> b = array @'[3] [6..8]
>>> pretty $ telecasts (Dims @'[1]) (Dims @'[0]) (concatenate (SNat @0)) a b
[[0,3,6],
 [1,4,7],
 [2,5,8]]

transmit :: forall sa sb sc a b c ds sib sic sob. (KnownNats sa, KnownNats sb, KnownNats sc, KnownNats ds, KnownNats sib, KnownNats sic, KnownNats sob, ds ~ Eval (EnumFromTo (Eval (Rank sa)) (Eval (Rank sb) - 1)), sib ~ Eval (DeleteDims ds sb), sob ~ Eval (GetDims ds sb), sb ~ Eval (InsertDims ds sob sib), sc ~ Eval (InsertDims ds sob sic), True ~ Eval (IsPrefixOf sa sb)) => (Array sa a -> Array sib b -> Array sic c) -> Array sa a -> Array sb b -> Array sc c Source #

Apply a binary array function to two arrays where the shape of the first array is a prefix of the second array.

>>> a = array @[2,3] [0..5]
>>> pretty $ transmit (zipWith (+)) (toScalar 1) a
[[1,2,3],
 [4,5,6]]

Row specializations

pattern (:<) :: forall s sh st a os ls ds. (KnownNats s, KnownNats sh, KnownNats st, True ~ Eval (InsertOk 0 st sh), s ~ Eval (IncAt 0 st), ds ~ '[0], sh ~ Eval (DeleteDims ds s), KnownNats ls, KnownNats os, Eval (SlicesOk ds os ls s) ~ True, os ~ Eval (Replicate (Eval (Rank ds)) 1), ls ~ Eval (GetLastPositions ds s), st ~ Eval (SetDims ds ls s)) => Array sh a -> Array st a -> Array s a infix 5 Source #

Convenience pattern for row extraction and consolidation at the beginning of an Array.

>>> (x:<xs) = array @'[4] [0..3]
>>> toDynamic x
UnsafeArray [] [0]
>>> toDynamic xs
UnsafeArray [3] [1,2,3]
>>> toDynamic (x:<xs)
UnsafeArray [4] [0,1,2,3]

cons :: forall st s sh a. (KnownNats st, KnownNats s, KnownNats sh, True ~ Eval (InsertOk 0 st sh), s ~ Eval (IncAt 0 st), sh ~ Eval (DeleteDim 0 st)) => Array sh a -> Array st a -> Array s a Source #

Add a new row

>>> pretty $ cons (array @'[2] [0,1]) (array @[2,2] [2,3,4,5])
[[0,1],
 [2,3],
 [4,5]]

uncons :: forall a s sh st ls os ds. (KnownNats s, KnownNats sh, KnownNats st, ds ~ '[0], sh ~ Eval (DeleteDims ds s), KnownNats ls, KnownNats os, os ~ Eval (Replicate (Eval (Rank ds)) 1), ls ~ Eval (GetLastPositions ds s), Eval (SlicesOk ds os ls s) ~ True, st ~ Eval (SetDims ds ls s)) => Array s a -> (Array sh a, Array st a) Source #

split an array into the first row and the remaining rows.

>>> import Data.Bifunctor (bimap)
>>> bimap toDynamic toDynamic $ uncons (array @[3,2] [0..5])
(UnsafeArray [2] [0,1],UnsafeArray [2,2] [2,3,4,5])

pattern (:>) :: forall si sl s a ds ls os. (KnownNats si, KnownNats sl, KnownNats s, True ~ Eval (InsertOk 0 si sl), s ~ Eval (IncAt 0 si), KnownNats ds, KnownNats ls, KnownNats os, sl ~ Eval (DeleteDim 0 si), ds ~ '[0], Eval (SlicesOk ds os ls s) ~ True, os ~ Eval (Replicate (Eval (Rank ds)) 0), ls ~ Eval (GetLastPositions ds s), si ~ Eval (SetDims ds ls s), sl ~ Eval (DeleteDims ds s)) => Array si a -> Array sl a -> Array s a infix 5 Source #

Convenience pattern for row extraction and consolidation at the end of an Array.

>>> (xs:>x) = array @'[4] [0..3]
>>> toDynamic x
UnsafeArray [] [3]
>>> toDynamic xs
UnsafeArray [3] [0,1,2]
>>> toDynamic (xs:>x)
UnsafeArray [4] [0,1,2,3]

snoc :: forall si s sl a. (KnownNats si, KnownNats s, KnownNats sl, True ~ Eval (InsertOk 0 si sl), s ~ Eval (IncAt 0 si), sl ~ Eval (DeleteDim 0 si)) => Array si a -> Array sl a -> Array s a Source #

Add a new row at the end

>>> pretty $ snoc (array @[2,2] [0,1,2,3]) (array @'[2] [4,5])
[[0,1],
 [2,3],
 [4,5]]

unsnoc :: forall ds os s a ls si sl. (KnownNats s, KnownNats ds, KnownNats si, KnownNats ls, KnownNats os, KnownNats sl, ds ~ '[0], Eval (SlicesOk ds os ls s) ~ True, os ~ Eval (Replicate (Eval (Rank ds)) 0), ls ~ Eval (GetLastPositions ds s), si ~ Eval (SetDims ds ls s), sl ~ Eval (DeleteDims ds s)) => Array s a -> (Array si a, Array sl a) Source #

split an array into the initial rows and the last row.

>>> import Data.Bifunctor (bimap)
>>> bimap toDynamic toDynamic $ unsnoc (array @[3,2] [0..5])
(UnsafeArray [2,2] [0,1,2,3],UnsafeArray [2] [4,5])

Shape specializations

type Vector s a = Array '[s] a Source #

A one-dimensional array.

vector :: forall n a t. (FromVector t a, KnownNat n) => t -> Array '[n] a Source #

Create a one-dimensional array.

>>> pretty $ vector @3 @Int [2,3,4]
[2,3,4]

vector' :: forall a n t. FromVector t a => SNat n -> t -> Array '[n] a Source #

vector with an explicit SNat rather than a KnownNat constraint.

>>> pretty $ vector' @Int (SNat @3) [2,3,4]
[2,3,4]

iota :: forall n. KnownNat n => Vector n Int Source #

Vector specialisation of range

>>> toDynamic $ iota @5
UnsafeArray [5] [0,1,2,3,4]

type Matrix m n a = Array '[m, n] a Source #

A two-dimensional array.

Math

uniform :: forall s a g m. (StatefulGen g m, UniformRange a, KnownNats s) => g -> (a, a) -> m (Array s a) Source #

Generate an array of uniform random variates between a range.

>>> import System.Random.Stateful hiding (uniform)
>>> g <- newIOGenM (mkStdGen 42)
>>> u <- uniform @[2,3,4] @Int g (0,9)
>>> pretty u
[[[0,7,0,2],
  [1,7,4,2],
  [5,9,8,2]],
 [[9,8,1,0],
  [2,2,8,2],
  [2,8,0,6]]]

invtri :: forall a n. (KnownNat n, Floating a, Eq a) => Matrix n n a -> Matrix n n a Source #

Inversion of a Triangular Matrix

>>> t = array @[3,3] @Double [1,0,1,0,1,2,0,0,1]
>>> pretty (invtri t)
[[1.0,0.0,-1.0],
 [0.0,1.0,-2.0],
 [0.0,0.0,1.0]]
>>> ident == mult t (invtri t)
True

inverse :: (Eq a, Floating a, KnownNat m) => Matrix m m a -> Matrix m m a Source #

Inverse of a square matrix.

A.mult (D.inverse a) a == a
>>> e = array @[3,3] @Double [4,12,-16,12,37,-43,-16,-43,98]
>>> pretty (inverse e)
[[49.36111111111111,-13.555555555555554,2.1111111111111107],
 [-13.555555555555554,3.7777777777777772,-0.5555555555555555],
 [2.1111111111111107,-0.5555555555555555,0.1111111111111111]]

chol :: (KnownNat m, Floating a) => Matrix m m a -> Matrix m m a Source #

Cholesky decomposition using the Cholesky-Crout algorithm.

>>> e = array @[3,3] @Double [4,12,-16,12,37,-43,-16,-43,98]
>>> pretty (chol e)
[[2.0,0.0,0.0],
 [6.0,1.0,0.0],
 [-8.0,5.0,3.0]]
>>> mult (chol e) (transpose (chol e)) == e
True