APL
An APL library for Haskell[edit]
APL is an array language with a highly-functional flavour, and a rich set of carefully-thought-out array operations. It would be interesting to build a Haskell library that offered a Haskell rendering of APL's array algebra, possibly (though not definitely) bound to a mature implementation.
This page collects thoughts loosely based around that idea.
APL arrays in Haskell[edit]
data Array elt -- Forces uniform element types
- Need rank-zero arrays
- In a rank-3 arrary, any of the axes can have zero length
e.g. (3 x 0 x 4) array /= (0 x 0 x 4) array
- Prototypical item? Leave open for now. A minefield.
Major question: should the rank be visible in the type at all? Plan A: data Array elt Plan (Succ A): data Array rank elt
The main API, using Plan A[edit]
data Array a -- Rectangular!
type Scalar a = Array a -- Rank 0, length 1
type Vector a = Array a -- Rank 1!
type Matrix a = Array a -- Rank 2!
type Axis = Nat
-- Arrays can be added, multiplied, etc
class Num a where
(+) :: Num a => a -> a ->
instance Num a => Num (Array a) where ..
-- All indexing is 0-based (Dijkstra)
Basic operations
-- A rank-0 array contains one item
zilde :: Vector a -- Empty vector, rank 1
enclose :: a -> Scalar a -- Returns a rank 0 array, of
-- depth one greater than input
encloseA :: Nat -- r
-> Array a -- Rank n
-> Array (Array a) -- Outer rank r, inner rank n-r
-- encloseA 2 (Array [3,1,4]) : Array [3] (Array [1,4])
-- enclose a = encloseA 0 (when a is an array)
disclose :: Scalar a -> Array a
discloseA :: Array (Array a) -> Array a
iota :: Nat -> Array Nat -- iota n = [0 1 2 3 ... n-1]
ravel :: Array a -> Vector a -- Flattens an array of arbitrary rank
-- (including zero!) in row-major order
-- Does not change depth
reshape :: Vector Nat -- s: the shape
-> Array a -- Arbitrary shape
-> Array a -- Shape of result = s
-- NB: ravel a = product (shape a) `reshape` a
product :: Num a => a -> Array a -> Array a
productA :: Num a => Axis -> a -> Array a -> Array a
-- Result has rank one smaller than input
shape :: Array a -> Vector Nat
-- shape [[1 3] [5 2] [3 9]] = [3 2]
-- shape [3 2] = [2]
-- shape [2] = [1]
-- rank = shape . shape -- Rank 1 and shape [1]
-- Or we could have rank :: Array a -> Nat
Swapping rank and depth
rankOperator ::
-- This is in J and it is somehow lovely in a way
-- that ordinary mortals cannot understand
-- rankOp 1 (+) A B
-- Swapping rank and depth
-- Array [2,4,5,3] Float
-- --> Array [2,5] (Array [4,3] Float)
-- And the reverse!
rankOp rank-spec f = reshape rank-spec . f . unreshape rank-spec
transpose :: Vector Nat -- Permutation of (iota (rank arg))
-> Array a -- Arg
-> Array a
-- Permutes the axes
More operations
class Item a wher
depth :: a -> Nat
instance Item Float where
depth _ = 0
instance Item a => Item (Array a) where
depth _ = 1 + depth (undefined :: a)
catenate :: Array a -> Array a -> Array a
-- Concatenates on last axis (or first in J)
-- Checks for shape compatibility
catenateA :: Axis -> Array a -> Array a -> Array a
-- You can specify the axis
-- Swapping rank with depth
flatten :: Vector (Vector a) -> Array a
vector :: [a] -> Vector a
each :: (a -> b) -> Array a -> Array b
simpleIndex -- m [a;b]
:: Array a -- a: The array to index
-> Vector (Array Nat) -- i: Outer array is a tuple
-- of length = rank a
-> Array a -- shape result = shape i[0] x shape i[1] ....
simpleIndex a is = chooseIndex a (disclose (reduce (outer catenate) zilde is))
-- We aren't quite sure about this definition
reduce :: (Array a -> Array a -> Array a) -> Array a
-- All rank one smaller than input
-> Array a -- Input
-> Array a -- Rank one smaller than input
-- except that rank 0 input gives identity
reduceA :: Axis -> (a -> a -> a) -> a
-> Array a
-> Array a -- Rank one smaller than ieput
outer :: (a -> b -> c) -- Function argument
-> Array a -> Array b -- Two array arguments, arg1, arg2
-> Array c -- Shape result = shape arg1 ++ shape arg2
-- simpleIndex a (vector [enclose 3, enclose 4]) :: Array a (rank 0)
-- mat [3 ; 4]
chooseIndex -- m [b]
:: Array a -- a: The array to index
-> Array (Vector Nat) -- i: Inner arrays are the index tuples
-- of length = rank a
-> Array a -- shape result = shape i
Various monomorphic pick operators
pick1 :: Vector (Matrix (Vector a))
-> Array (Nat, (Nat,Nat), Nat)
-> Array a
pick2 :: Vector (Matrix a)
-> Array (Nat, (Nat,Nat))
-> Array a
-- Just an instance of pick2
pick2 :: Vector (Matrix (Vector a))
-> Array (Nat, (Nat,Nat))
-> Array (Vector a)
Reference implementation[edit]
This implementation of the above API is intended to give its semantics. It is not intended to run fast!
data Array a = Arr Shape [a]
type Shape = [Nat]
-- Invariant: Arr s xs: product s = length xs
ravel :: Array a -> Vector a
ravel (Arr s a) = Arr [product s] a
zilde :: Vector a -- Empty vector, rank 1
zilde = Arr [0] []
enclose :: a -> Scalar a -- Returns a rank 0 array, of
-- depth one greater than input
enclose x = Arr [] [x]
disclose :: Scalar a -> a
disclose (Arr [] [x]) = x
discloseA (Arr outer items)
= Arr (outer ++ inner) [ i | Arr _ is <- items, i <- is ]
where
(Arr inner _ : _) = items
transpose :: Vector Nat -- Permutation of (iota (rank arg))
-> Array a -- Arg
-> Array a
transpose (Arr [n] perm) (Arr shape items)
= assert (n == length shape ) $
Arr (permute perm shape)
(scramble ... items)
-- Property: disclose (enclose x) == x
shape :: Array a -> Vector Nat
shape (Arr s a) = Arr [1] s
reshape :: Vector Nat -- s: the shape
-> Array a -- Arbitrary shape
-> Array a -- Shape of result = s
reshape (Arr [n] s) (Arr s' elts)
| null elts = error "Reshape on empty array"
| otherwise
= Arr s (take (product s) (cycle elts))
each :: (a -> b) -> Array a -> Array b
each f (Arr s xs) = Arr s (map f xs)
reduce :: (Array a -> Array a -> Array a) -> Array a
-- All rank one smaller than input
-> Array a -- Input
-> Array a -- Rank one smaller than input
-- except that rank 0 input gives identity
reduce k z (Arr [] [item])
= Arr [] [item] -- Identity on rank 0
reduce k z (Arr (s:ss) items)
= foldr k z (chop ss items)
encloseA :: Nat -> Array a -> Array a
encloseA n (Arr shape items)
= Arr outer_shape (chop inner_shape items)
where
(outer_shape, inner_shape) = splitAt n shape
chop :: Shape -> [item] -> [Array item]
chop s [] = []
chop s is = Arr s i : chop s is'
where
(i,is') = splitAt (product s) is
A couple of examples[edit]
x = 0 1 2 : Array Float = Arr [2,3] [0,1,2,3,4,5] 3 4 5
enclose x :: Array (Array Float) = Arr [] [Arr [2,3] [0,1,2,3,4,5]]