numhask-array-0.3.0.1: n-dimensional arrays

Safe HaskellNone
LanguageHaskell2010

NumHask.Array.Constraints

Synopsis

Documentation

type family IsValidConcat i (a :: [Nat]) (b :: [Nat]) :: Bool where ... Source #

Equations

IsValidConcat _ '[] _ = False 
IsValidConcat _ _ '[] = False 
IsValidConcat i a b = And (ZipWith (==@#@$) (DropDim i a) (DropDim i b)) 

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

Equations

Squeeze '[] = '[] 
Squeeze a = Filter ((/=@#@$$) 1) a 

type family Concatenate i (a :: [Nat]) (b :: [Nat]) :: [Nat] where ... Source #

Equations

Concatenate i a b = Take i (Fst (SplitAt (i + 1) a)) ++ ('[Head (Drop i a) + Head (Drop i b)] ++ Snd (SplitAt (i + 1) b)) 

type family IsValidTranspose (p :: [Nat]) (a :: [Nat]) :: Bool where ... Source #

Equations

IsValidTranspose p a = (Minimum p >= 0) && ((Minimum a >= 0) && ((Sum a == Sum p) && (Length p == Length a))) 

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

Reduces axis i in shape s. Does not maintain singlton dimension.

Equations

Fold _ '[] = '[] 
Fold d xs = Take d (Fst (SplitAt (d + 1) xs)) ++ Snd (SplitAt (d + 1) xs) 

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

Reduces axis i in shape s. Maintains singlton dimension

Equations

FoldAlong _ '[] = '[] 
FoldAlong d xs = Take d (Fst (SplitAt (d + 1) xs)) ++ ('[1] ++ Snd (SplitAt (d + 1) xs)) 

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

Equations

TailModule _ '[] = '[] 
TailModule d xs = Snd (SplitAt d xs) 

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

Equations

HeadModule _ '[] = '[] 
HeadModule d xs = Fst (SplitAt d xs) 

type family Transpose a where ... Source #

Equations

Transpose a = Reverse a