orthotope-0.1.2.0: Multidimensional arrays inspired by APL
Safe HaskellNone
LanguageHaskell2010

Data.Array.Internal.Shape

Synopsis

Documentation

class Broadcast'' (o :: Ordering) (i :: Nat) (d :: Nat) (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where Source #

Instances

Instances details
(TypeError ('Text "unordered dimensions") :: Constraint) => Broadcast'' 'GT i d ds sh rsh Source # 
Instance details

Defined in Data.Array.Internal.Shape

Broadcast' (i + 1) (d ': ds) sh rsh => Broadcast'' 'LT i d ds sh (s' ': rsh) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Broadcast' (i + 1) ds sh rsh => Broadcast'' 'EQ i d ds (s ': sh) (s ': rsh) Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Broadcast' (i :: Nat) (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where Source #

Instances

Instances details
Broadcast' i ('[] :: [Nat]) ('[] :: [Nat]) ('[] :: [Nat]) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Broadcast' i ('[] :: [Nat]) ('[] :: [Nat]) sh' => Broadcast' i ('[] :: [Nat]) ('[] :: [Nat]) (s ': sh') Source # 
Instance details

Defined in Data.Array.Internal.Shape

(TypeError ('Text "Too few dimension indices") :: Constraint) => Broadcast' i ('[] :: [Nat]) (s ': sh) sh' Source # 
Instance details

Defined in Data.Array.Internal.Shape

(TypeError ('Text "Too many dimensions indices") :: Constraint) => Broadcast' i (d ': ds) ('[] :: [Nat]) sh' Source # 
Instance details

Defined in Data.Array.Internal.Shape

(TypeError ('Text "Too few result dimensions") :: Constraint) => Broadcast' i (d ': ds) (s ': sh) ('[] :: [Nat]) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Broadcast'' (CmpNat i d) i d ds (s ': sh) (s' ': sh') => Broadcast' i (d ': ds) (s ': sh) (s' ': sh') Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Broadcast (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where Source #

Using the dimension indices ds, can sh be broadcast into shape sh'?

Instances

Instances details
Broadcast' 0 ds sh sh' => Broadcast ds sh sh' Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Typeable s => Shape (s :: [Nat]) where Source #

Methods

shapeP :: Proxy s -> [Int] Source #

sizeP :: Proxy s -> Int Source #

Instances

Instances details
Shape ('[] :: [Nat]) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

shapeP :: Proxy '[] -> [Int] Source #

sizeP :: Proxy '[] -> Int Source #

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

Defined in Data.Array.Internal.Shape

Methods

shapeP :: Proxy (n ': s) -> [Int] Source #

sizeP :: Proxy (n ': s) -> Int Source #

class Slice (ls :: [(Nat, Nat)]) (ss :: [Nat]) (rs :: [Nat]) | ls ss -> rs where Source #

Methods

sliceOffsets :: Proxy ls -> Proxy ss -> [Int] Source #

Instances

Instances details
Slice ('[] :: [(Nat, Nat)]) ss ss Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

sliceOffsets :: Proxy '[] -> Proxy ss -> [Int] Source #

(Slice ls ss rs, (o + n) <= s, KnownNat o) => Slice ('(o, n) ': ls) (s ': ss) (n ': rs) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

sliceOffsets :: Proxy ('(o, n) ': ls) -> Proxy (s ': ss) -> [Int] Source #

class Stride (ts :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ts ss -> rs Source #

Instances

Instances details
Stride ('[] :: [Nat]) ss ss Source # 
Instance details

Defined in Data.Array.Internal.Shape

(Stride ts ss rs, DivRoundUp s t ~ r) => Stride (t ': ts) (s ': ss) (r ': rs) Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Window' (ows :: [Nat]) (ws :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ows ws ss -> rs Source #

Instances

Instances details
(ows ++ ss) ~ rs => Window' ows ('[] :: [Nat]) ss rs Source # 
Instance details

Defined in Data.Array.Internal.Shape

(Window' ows ws ss rs, w <= s, ((s + 1) - w) ~ r) => Window' ows (w ': ws) (s ': ss) (r ': rs) Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Window (ws :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ws ss -> rs Source #

Instances

Instances details
Window' ws ws ss rs => Window ws ss rs Source # 
Instance details

Defined in Data.Array.Internal.Shape

class ValidDims (rs :: [Nat]) (sh :: [Nat]) Source #

Instances

Instances details
AllElem rs (Count 0 sh) => ValidDims rs sh Source # 
Instance details

Defined in Data.Array.Internal.Shape

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

Equations

Index (x ': xs) 0 = x 
Index (x ': xs) i = Index xs (i - 1) 

type family Permute' (is :: [Nat]) (xs :: [Nat]) where ... Source #

Equations

Permute' '[] xs = '[] 
Permute' (i ': is) xs = Index xs i ': Permute' is xs 

type Permute (is :: [Nat]) (xs :: [Nat]) = Permute' is (Take (Rank is) xs) ++ Drop (Rank is) xs Source #

class Elem' (e :: Ordering) (i :: Nat) (ns :: [Nat]) Source #

Instances

Instances details
Elem i ns => Elem' 'LT i ns Source # 
Instance details

Defined in Data.Array.Internal.Shape

Elem' 'EQ i ns Source # 
Instance details

Defined in Data.Array.Internal.Shape

Elem i ns => Elem' 'GT i ns Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Elem (i :: Nat) (ns :: [Nat]) Source #

Instances

Instances details
Elem' (CmpNat i n) i ns => Elem i (n ': ns) Source # 
Instance details

Defined in Data.Array.Internal.Shape

class AllElem (is :: [Nat]) (ns :: [Nat]) Source #

Instances

Instances details
AllElem ('[] :: [Nat]) ns Source # 
Instance details

Defined in Data.Array.Internal.Shape

(Elem i ns, AllElem is ns) => AllElem (i ': is) ns Source # 
Instance details

Defined in Data.Array.Internal.Shape

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

Equations

Count i '[] = '[] 
Count i (x ': xs) = i ': Count (i + 1) xs 

class Permutation (is :: [Nat]) Source #

Instances

Instances details
AllElem is (Count 0 is) => Permutation is Source # 
Instance details

Defined in Data.Array.Internal.Shape

class Padded (ps :: [(Nat, Nat)]) (sh :: [Nat]) (sh' :: [Nat]) | ps sh -> sh' where Source #

Methods

padded :: Proxy ps -> Proxy sh -> [(Int, Int)] Source #

Instances

Instances details
Padded ('[] :: [(Nat, Nat)]) sh sh Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

padded :: Proxy '[] -> Proxy sh -> [(Int, Int)] Source #

(KnownNat l, KnownNat h, ((l + s) + h) ~ s', Padded ps sh sh') => Padded ('(l, h) ': ps) (s ': sh) (s' ': sh') Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

padded :: Proxy ('(l, h) ': ps) -> Proxy (s ': sh) -> [(Int, Int)] Source #

class BoolVal (b :: Bool) where Source #

Methods

boolVal :: Proxy b -> Bool Source #

Instances

Instances details
BoolVal 'False Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

boolVal :: Proxy 'False -> Bool Source #

BoolVal 'True Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

boolVal :: Proxy 'True -> Bool Source #

type family Stretch (s :: Nat) (m :: Nat) :: Bool where ... Source #

Equations

Stretch 1 m = 'True 
Stretch m m = 'False 
Stretch s m = TypeError ((('Text "Cannot stretch " :<>: 'ShowType s) :<>: 'Text " to ") :<>: 'ShowType m) 

class ValidStretch (from :: [Nat]) (to :: [Nat]) where Source #

Methods

stretching :: Proxy from -> Proxy to -> [Bool] Source #

Instances

Instances details
ValidStretch ('[] :: [Nat]) ('[] :: [Nat]) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

stretching :: Proxy '[] -> Proxy '[] -> [Bool] Source #

(BoolVal (Stretch s m), ValidStretch ss ms) => ValidStretch (s ': ss) (m ': ms) Source # 
Instance details

Defined in Data.Array.Internal.Shape

Methods

stretching :: Proxy (s ': ss) -> Proxy (m ': ms) -> [Bool] Source #

type family Init (xs :: [Nat]) where ... Source #

Equations

Init '[x] = '[] 
Init (x ': xs) = x ': Init xs 

type family Last (xs :: [Nat]) where ... Source #

Equations

Last '[x] = x 
Last (x ': xs) = Last xs 

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

Equations

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

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

Equations

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

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

Equations

'[] ++ ys = ys 
(x ': xs) ++ ys = x ': (xs ++ ys) 

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

Equations

Size' a '[] = a 
Size' a (n ': ns) = Size' (a * n) ns 

type Size (s :: [Nat]) = Size' 1 s Source #

Compute the size, i.e., total number of elements of a type level shape.

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

Compute the rank, i.e., length of a type level shape.

Equations

Rank '[] = 0 
Rank (n ': ns) = 1 + Rank ns 

type DivRoundUp n m = Div ((n + m) - 1) m Source #

shapeT :: forall sh. Shape sh => [Int] Source #

sizeT :: forall sh. Shape sh => Int Source #

withShapeP :: [Int] -> (forall sh. Shape sh => Proxy sh -> r) -> r Source #

Turn a dynamic shape back into a type level shape. withShape sh shapeP == sh

withShape :: [Int] -> (forall sh. Shape sh => r) -> r Source #