| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- newtype Shape (s :: [Nat]) = Shape {}
- class HasShape s where
- type family (a :: [k]) ++ (b :: [k]) :: [k] where ...
- type family (a :: [k]) !! (b :: Nat) :: k where ...
- type family Take (n :: Nat) (a :: [k]) :: [k] where ...
- type family Drop (n :: Nat) (a :: [k]) :: [k] where ...
- type Reverse (a :: [k]) = ReverseGo a '[]
- type family ReverseGo (a :: [k]) (b :: [k]) :: [k] where ...
- type family Filter (r :: [Nat]) (xs :: [Nat]) (i :: Nat) where ...
- rank :: [a] -> Int
- type family Rank (s :: [a]) :: Nat where ...
- ranks :: [[a]] -> [Int]
- type family Ranks (s :: [[a]]) :: [Nat] where ...
- size :: [Int] -> Int
- type family Size (s :: [Nat]) :: Nat where ...
- dimension :: [Int] -> Int -> Int
- type family Dimension (s :: [Nat]) (i :: Nat) :: Nat where ...
- flatten :: [Int] -> [Int] -> Int
- shapen :: [Int] -> Int -> [Int]
- minimum :: [Int] -> Int
- type family Minimum (s :: [Nat]) :: Nat where ...
- checkIndex :: Int -> Int -> Bool
- type family CheckIndex (i :: Nat) (n :: Nat) :: Bool where ...
- checkIndexes :: [Int] -> Int -> Bool
- type family CheckIndexes (i :: [Nat]) (n :: Nat) :: Bool where ...
- addIndex :: [Int] -> Int -> Int -> [Int]
- type AddIndex s i d = Take i s ++ (d ': Drop i s)
- dropIndex :: [Int] -> Int -> [Int]
- type DropIndex s i = Take i s ++ Drop (i + 1) s
- posRelative :: [Int] -> [Int]
- type family PosRelative (s :: [Nat]) where ...
- type family PosRelativeGo (r :: [Nat]) (s :: [Nat]) where ...
- addIndexes :: [Int] -> [Int] -> [Int] -> [Int]
- type family AddIndexes (as :: [Nat]) (xs :: [Nat]) (ys :: [Nat]) where ...
- type family AddIndexesGo (as :: [Nat]) (xs :: [Nat]) (ys :: [Nat]) where ...
- dropIndexes :: [Int] -> [Int] -> [Int]
- type family DropIndexes (s :: [Nat]) (i :: [Nat]) where ...
- takeIndexes :: [Int] -> [Int] -> [Int]
- type family TakeIndexes (s :: [Nat]) (i :: [Nat]) where ...
- exclude :: Int -> [Int] -> [Int]
- type family Exclude (r :: Nat) (i :: [Nat]) where ...
- concatenate' :: Int -> [Int] -> [Int] -> [Int]
- type Concatenate i s0 s1 = Take i s0 ++ ((Dimension s0 i + Dimension s1 i) ': Drop (i + 1) s0)
- type CheckConcatenate i s0 s1 s = (CheckIndex i (Rank s0) && ((DropIndex s0 i == DropIndex s1 i) && (Rank s0 == Rank s1))) ~ 'True
- type Insert d s = Take d s ++ ((Dimension s d + 1) ': Drop (d + 1) s)
- type CheckInsert d i s = (CheckIndex d (Rank s) && CheckIndex i (Dimension s d)) ~ 'True
- reorder' :: [Int] -> [Int] -> [Int]
- type family Reorder (s :: [Nat]) (ds :: [Nat]) :: [Nat] where ...
- type family CheckReorder (ds :: [Nat]) (s :: [Nat]) where ...
- squeeze' :: (Eq a, Multiplicative a) => [a] -> [a]
- type family Squeeze (a :: [Nat]) where ...
- incAt :: Int -> [Int] -> [Int]
- decAt :: Int -> [Int] -> [Int]
- class KnownNats (ns :: [Nat]) where
- class KnownNatss (ns :: [[Nat]]) where
Documentation
newtype Shape (s :: [Nat]) Source #
The Shape type holds a [Nat] at type level and the equivalent [Int] at value level. Using [Int] as the index for an array nicely represents the practical interests and constraints downstream of this high-level API: densely-packed numbers (reals or integrals), indexed and layered.
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
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 '[] _ = 'True | |
| CheckIndexes (i ': is) n = CheckIndex i n && CheckIndexes is n | 
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]
dropIndex :: [Int] -> Int -> [Int] Source #
drop the i'th dimension from a shape
>>>dropIndex [2, 3, 4] 1[2,4]
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) | 
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") | 
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) | 
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 | 
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 #
concatenate
>>>concatenate' 1 [2,3,4] [2,3,4][2,6,4]
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 #
reorder' :: [Int] -> [Int] -> [Int] Source #
reorder' s i reorders the dimensions of shape s according to a list of positions i
>>>reorder' [2,3,4] [2,0,1][4,2,3]
type family CheckReorder (ds :: [Nat]) (s :: [Nat]) where ... Source #
squeeze' :: (Eq a, Multiplicative a) => [a] -> [a] Source #
remove 1's from a list
class KnownNatss (ns :: [[Nat]]) where Source #
Reflect a list of list of Nats
Instances
| KnownNatss ('[] :: [[Nat]]) Source # | |
| (KnownNats n, KnownNatss ns) => KnownNatss (n ': ns) Source # | |