numhask-array-0.4.0.0: n-dimensional arrays

Safe HaskellNone
LanguageHaskell2010

NumHask.Array.Shape

Description

Functions for manipulating shape. The module tends to supply equivalent functionality at type-level and value-level with functions of the same name (except for capitalization).

Synopsis

Documentation

newtype Shape (s :: [Nat]) Source #

The Shape type holds a [Nat] at type level and the equivalent [Int] at value level.

Constructors

Shape 

Fields

Instances
Show (Shape s) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

showsPrec :: Int -> Shape s -> ShowS #

show :: Shape s -> String #

showList :: [Shape s] -> ShowS #

class HasShape s where Source #

Methods

toShape :: Shape s Source #

Instances
HasShape ([] :: [Nat]) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

toShape :: Shape [] Source #

(KnownNat n, HasShape s) => HasShape (n ': s) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

toShape :: Shape (n ': s) Source #

rank :: [a] -> Int Source #

Number of dimensions

type family Rank (s :: [a]) :: Nat where ... Source #

Equations

Rank '[] = 0 
Rank (_ ': s) = Rank s + 1 

ranks :: [[a]] -> [Int] Source #

The shape of a list of element indexes

type family Ranks (s :: [[a]]) :: [Nat] where ... Source #

Equations

Ranks '[] = '[] 
Ranks (x ': xs) = Rank x ': Ranks xs 

size :: [Int] -> Int Source #

Number of elements

type family Size (s :: [Nat]) :: Nat where ... Source #

Equations

Size '[] = 1 
Size (n ': s) = n * Size s 

flatten :: [Int] -> [Int] -> Int Source #

convert from n-dim shape index to a flat index

>>> flatten [2,3,4] [1,1,1]
17
>>> flatten [] [1,1,1]
0

shapen :: [Int] -> Int -> [Int] Source #

convert from a flat index to a shape index

>>> shapen [2,3,4] 17
[1,1,1]

checkIndex :: Int -> Int -> Bool Source #

checkIndex i n checks if i is a valid index of a list of length n

type family CheckIndex (i :: Nat) (n :: Nat) :: Bool where ... Source #

Equations

CheckIndex i n = If ((0 <=? i) && ((i + 1) <=? n)) True (TypeError (Text "index outside range")) 

checkIndexes :: [Int] -> Int -> Bool Source #

checkIndexes is n check if is are valid indexes of a list of length n

type family CheckIndexes (i :: [Nat]) (n :: Nat) :: Bool where ... Source #

Equations

CheckIndexes '[] n = True 
CheckIndexes (i ': is) n = CheckIndex i n && CheckIndexes is n 

dimension :: [Int] -> Int -> Int Source #

dimension i is the i'th dimension of a Shape

type family Dimension (s :: [Nat]) (i :: Nat) :: Nat where ... Source #

Equations

Dimension (s ': _) 0 = s 
Dimension (_ ': s) n = Dimension s (n - 1) 
Dimension _ _ = TypeError (Text "dimension overflow") 

minimum :: [Int] -> Int Source #

minimum value in a list

type family Minimum (s :: [Nat]) :: Nat where ... Source #

Equations

Minimum '[] = TypeError (Text "zero dimension") 
Minimum '[x] = x 
Minimum (x ': xs) = If (x <=? Minimum xs) x (Minimum xs) 

type family Take (n :: Nat) (a :: [k]) :: [k] where ... Source #

Equations

Take 0 _ = '[] 
Take n (x ': xs) = x ': Take (n - 1) xs 

type family Drop (n :: Nat) (a :: [k]) :: [k] where ... Source #

Equations

Drop 0 xs = xs 
Drop n (_ ': xs) = Drop (n - 1) xs 

type family Tail (a :: [k]) :: [k] where ... Source #

Equations

Tail '[] = TypeError (Text "No tail") 
Tail (_ ': xs) = xs 

type family Init (a :: [k]) :: [k] where ... Source #

Equations

Init '[] = TypeError (Text "No init") 
Init '[_] = '[] 
Init (x ': xs) = x ': Init xs 

type family Head (a :: [k]) :: k where ... Source #

Equations

Head '[] = TypeError (Text "No head") 
Head (x ': _) = x 

type family Last (a :: [k]) :: k where ... Source #

Equations

Last '[] = TypeError (Text "No last") 
Last '[x] = x 
Last (_ ': xs) = Last xs 

type family (a :: [k]) ++ (b :: [k]) :: [k] where ... Source #

Equations

'[] ++ b = b 
(a ': as) ++ b = a ': (as ++ b) 

dropIndex :: [Int] -> Int -> [Int] Source #

drop the i'th dimension from a shape

>>> dropIndex [2, 3, 4] 1
[2,4]

type DropIndex s i = Take i s ++ Drop (i + 1) s Source #

addIndex :: [Int] -> Int -> Int -> [Int] Source #

addIndex s i d adds a new dimension to shape s at position i

>>> addIndex [2,4] 1 3
[2,3,4]

type AddIndex s i d = Take i s ++ (d ': Drop i s) Source #

type Reverse (a :: [k]) = ReverseGo a '[] Source #

type family ReverseGo (a :: [k]) (b :: [k]) :: [k] where ... Source #

Equations

ReverseGo '[] b = b 
ReverseGo (a ': as) b = ReverseGo as (a ': b) 

posRelative :: [Int] -> [Int] Source #

convert a list of position that references a final shape to one that references positions relative to an accumulator. Deletions are from the left and additions are from the right.

deletions

>>> posRelative [0,1]
[0,0]

additions

>>> reverse (posRelative (reverse [1,0]))
[0,0]

type family PosRelative (s :: [Nat]) where ... Source #

Equations

PosRelative s = PosRelativeGo s '[] 

type family PosRelativeGo (r :: [Nat]) (s :: [Nat]) where ... Source #

Equations

PosRelativeGo '[] r = Reverse r 
PosRelativeGo (x ': xs) r = PosRelativeGo (DecMap x xs) (x ': r) 

type family DecMap (x :: Nat) (ys :: [Nat]) :: [Nat] where ... Source #

Equations

DecMap _ '[] = '[] 
DecMap x (y ': ys) = If ((y + 1) <=? x) y (y - 1) ': DecMap x ys 

dropIndexes :: [Int] -> [Int] -> [Int] Source #

drop dimensions of a shape according to a list of positions (where position refers to the initial shape)

>>> dropIndexes [2, 3, 4] [1, 0]
[4]

type family DropIndexes (s :: [Nat]) (i :: [Nat]) where ... Source #

Equations

DropIndexes s i = DropIndexesGo s (PosRelative i) 

type family DropIndexesGo (s :: [Nat]) (i :: [Nat]) where ... Source #

Equations

DropIndexesGo s '[] = s 
DropIndexesGo s (i ': is) = DropIndexesGo (DropIndex s i) is 

addIndexes :: [Int] -> [Int] -> [Int] -> [Int] Source #

insert a list of dimensions according to position and dimension lists. Note that the list of positions references the final shape and not the initial shape.

>>> addIndexes [4] [1,0] [3,2]
[2,3,4]

type family AddIndexes (as :: [Nat]) (xs :: [Nat]) (ys :: [Nat]) where ... Source #

Equations

AddIndexes as xs ys = AddIndexesGo as (Reverse (PosRelative (Reverse xs))) ys 

type family AddIndexesGo (as :: [Nat]) (xs :: [Nat]) (ys :: [Nat]) where ... Source #

Equations

AddIndexesGo as' '[] _ = as' 
AddIndexesGo as' (x ': xs') (y ': ys') = AddIndexesGo (AddIndex as' x y) xs' ys' 
AddIndexesGo _ _ _ = TypeError (Text "mismatched ranks") 

takeIndexes :: [Int] -> [Int] -> [Int] Source #

take list of dimensions according to position lists.

>>> takeIndexes [2,3,4] [2,0]
[4,2]

type family TakeIndexes (s :: [Nat]) (i :: [Nat]) where ... Source #

Equations

TakeIndexes '[] _ = '[] 
TakeIndexes _ '[] = '[] 
TakeIndexes s (i ': is) = (s !! i) ': TakeIndexes s is 

type family (a :: [k]) !! (b :: Nat) :: k where ... Source #

Equations

'[] !! i = TypeError (Text "Index Underflow") 
(x ': _) !! 0 = x 
(_ ': xs) !! i = (!!) xs (i - 1) 

type family Enumerate (n :: Nat) where ... Source #

Equations

Enumerate n = Reverse (EnumerateGo n) 

type family EnumerateGo (n :: Nat) where ... Source #

Equations

EnumerateGo 0 = '[] 
EnumerateGo n = (n - 1) ': EnumerateGo (n - 1) 

exclude :: Int -> [Int] -> [Int] Source #

turn a list of included positions for a given rank into a list of excluded positions

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

type family Exclude (r :: Nat) (i :: [Nat]) where ... Source #

Equations

Exclude r i = DropIndexes (EnumerateGo r) i 

concatenate' :: Int -> [Int] -> [Int] -> [Int] Source #

type Concatenate i s0 s1 = Take i s0 ++ ((Dimension s0 i + Dimension s1 i) ': Drop (i + 1) s0) Source #

type CheckConcatenate i s0 s1 s = (CheckIndex i (Rank s0) && ((DropIndex s0 i == DropIndex s1 i) && (Rank s0 == Rank s1))) ~ True Source #

type CheckInsert d i s = (CheckIndex d (Rank s) && CheckIndex i (Dimension s d)) ~ True Source #

type Insert d s = Take d s ++ ((Dimension s d + 1) ': Drop (d + 1) s) Source #

incAt :: Int -> [Int] -> [Int] Source #

incAt d s increments the index at d of shape s by one.

decAt :: Int -> [Int] -> [Int] Source #

decAt d s decrements the index at d of shape s by one.

reorder' :: [Int] -> [Int] -> [Int] Source #

type family Reorder (s :: [Nat]) (ds :: [Nat]) :: [Nat] where ... Source #

Equations

Reorder '[] _ = '[] 
Reorder _ '[] = '[] 
Reorder s (d ': ds) = Dimension s d ': Reorder s ds 

type family CheckReorder (ds :: [Nat]) (s :: [Nat]) where ... Source #

Equations

CheckReorder ds s = If ((Rank ds == Rank s) && CheckIndexes ds (Rank s)) True (TypeError (Text "bad dimensions")) ~ True 

squeeze' :: (Eq a, Num a) => [a] -> [a] Source #

type family Squeeze (a :: [Nat]) where ... Source #

Equations

Squeeze '[] = '[] 
Squeeze a = Filter '[] a 1 

type family Filter (r :: [Nat]) (xs :: [Nat]) (i :: Nat) where ... Source #

Equations

Filter r '[] _ = Reverse r 
Filter r (x ': xs) i = Filter (If (x == i) r (x ': r)) xs i 

type family Sort (xs :: [k]) :: [k] where ... Source #

Equations

Sort '[] = '[] 
Sort (x ': xs) = (Sort (SFilter FMin x xs) ++ '[x]) ++ Sort (SFilter FMax x xs) 

data Flag Source #

Constructors

FMin 
FMax 

type family Cmp (a :: k) (b :: k) :: Ordering Source #

type family SFilter (f :: Flag) (p :: k) (xs :: [k]) :: [k] where ... Source #

Equations

SFilter f p '[] = '[] 
SFilter FMin p (x ': xs) = If (Cmp x p == LT) (x ': SFilter FMin p xs) (SFilter FMin p xs) 
SFilter FMax p (x ': xs) = If ((Cmp x p == GT) || (Cmp x p == EQ)) (x ': SFilter FMax p xs) (SFilter FMax p xs) 

type family Zip lst lst' where ... Source #

Equations

Zip lst lst' = ZipWith (,) lst lst' 

type family ZipWith f lst lst' where ... Source #

Equations

ZipWith f '[] lst = '[] 
ZipWith f lst '[] = '[] 
ZipWith f (l ': ls) (n ': ns) = f l n ': ZipWith f ls ns 

type family Fst a where ... Source #

Equations

Fst '(a, _) = a 

type family Snd a where ... Source #

Equations

Snd '(_, a) = a 

type family FMap f lst where ... Source #

Equations

FMap f '[] = '[] 
FMap f (l ': ls) = f l ': FMap f ls 

class KnownNats (ns :: [Nat]) where Source #

Reflect a list of Nats

Methods

natVals :: Proxy ns -> [Int] Source #

Instances
KnownNats ([] :: [Nat]) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

natVals :: Proxy [] -> [Int] Source #

(KnownNat n, KnownNats ns) => KnownNats (n ': ns) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

natVals :: Proxy (n ': ns) -> [Int] Source #

class KnownNatss (ns :: [[Nat]]) where Source #

Reflect a list of list of Nats

Methods

natValss :: Proxy ns -> [[Int]] Source #

Instances
KnownNatss ([] :: [[Nat]]) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

natValss :: Proxy [] -> [[Int]] Source #

(KnownNats n, KnownNatss ns) => KnownNatss (n ': ns) Source # 
Instance details

Defined in NumHask.Array.Shape

Methods

natValss :: Proxy (n ': ns) -> [[Int]] Source #