Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Broadcast'' (o :: Ordering) (i :: Nat) (d :: Nat) (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where
- broadcasting'' :: [Bool]
- class Broadcast' (i :: Nat) (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where
- broadcasting' :: [Bool]
- class Broadcast (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where
- broadcasting :: [Bool]
- class Typeable s => Shape (s :: [Nat]) where
- class Slice (ls :: [(Nat, Nat)]) (ss :: [Nat]) (rs :: [Nat]) | ls ss -> rs where
- sliceOffsets :: Proxy ls -> Proxy ss -> [Int]
- class Stride (ts :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ts ss -> rs
- class Window' (ows :: [Nat]) (ws :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ows ws ss -> rs
- class Window (ws :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ws ss -> rs
- class ValidDims (rs :: [Nat]) (sh :: [Nat])
- type family Index (xs :: [Nat]) (i :: Nat) where ...
- type family Permute' (is :: [Nat]) (xs :: [Nat]) where ...
- type Permute (is :: [Nat]) (xs :: [Nat]) = Permute' is (Take (Rank is) xs) ++ Drop (Rank is) xs
- class Elem' (e :: Ordering) (i :: Nat) (ns :: [Nat])
- class Elem (i :: Nat) (ns :: [Nat])
- class AllElem (is :: [Nat]) (ns :: [Nat])
- type family Count (i :: Nat) (xs :: [Nat]) :: [Nat] where ...
- class Permutation (is :: [Nat])
- class Padded (ps :: [(Nat, Nat)]) (sh :: [Nat]) (sh' :: [Nat]) | ps sh -> sh' where
- class BoolVal (b :: Bool) where
- type family Stretch (s :: Nat) (m :: Nat) :: Bool where ...
- class ValidStretch (from :: [Nat]) (to :: [Nat]) where
- stretching :: Proxy from -> Proxy to -> [Bool]
- type family Init (xs :: [Nat]) where ...
- type family Last (xs :: [Nat]) where ...
- type family Drop (n :: Nat) (xs :: [Nat]) :: [Nat] where ...
- type family Take (n :: Nat) (xs :: [Nat]) :: [Nat] where ...
- type family (xs :: [Nat]) ++ (ys :: [Nat]) :: [Nat] where ...
- type family Size' (a :: Nat) (s :: [Nat]) :: Nat where ...
- type Size (s :: [Nat]) = Size' 1 s
- type family Rank (s :: [Nat]) :: Nat where ...
- type DivRoundUp n m = Div ((n + m) - 1) m
- shapeT :: forall sh. Shape sh => [Int]
- sizeT :: forall sh. Shape sh => Int
- withShapeP :: [Int] -> (forall sh. Shape sh => Proxy sh -> r) -> r
- withShape :: [Int] -> (forall sh. Shape sh => r) -> r
Documentation
class Broadcast'' (o :: Ordering) (i :: Nat) (d :: Nat) (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where Source #
broadcasting'' :: [Bool] Source #
Instances
(TypeError ('Text "unordered dimensions") :: Constraint) => Broadcast'' 'GT i d ds sh rsh Source # | |
Defined in Data.Array.Internal.Shape broadcasting'' :: [Bool] Source # | |
Broadcast' (i + 1) (d ': ds) sh rsh => Broadcast'' 'LT i d ds sh (s' ': rsh) Source # | |
Defined in Data.Array.Internal.Shape broadcasting'' :: [Bool] Source # | |
Broadcast' (i + 1) ds sh rsh => Broadcast'' 'EQ i d ds (s ': sh) (s ': rsh) Source # | |
Defined in Data.Array.Internal.Shape broadcasting'' :: [Bool] Source # |
class Broadcast' (i :: Nat) (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where Source #
broadcasting' :: [Bool] Source #
Instances
Broadcast' i ('[] :: [Nat]) ('[] :: [Nat]) ('[] :: [Nat]) Source # | |
Defined in Data.Array.Internal.Shape broadcasting' :: [Bool] Source # | |
Broadcast' i ('[] :: [Nat]) ('[] :: [Nat]) sh' => Broadcast' i ('[] :: [Nat]) ('[] :: [Nat]) (s ': sh') Source # | |
Defined in Data.Array.Internal.Shape broadcasting' :: [Bool] Source # | |
(TypeError ('Text "Too few dimension indices") :: Constraint) => Broadcast' i ('[] :: [Nat]) (s ': sh) sh' Source # | |
Defined in Data.Array.Internal.Shape broadcasting' :: [Bool] Source # | |
(TypeError ('Text "Too many dimensions indices") :: Constraint) => Broadcast' i (d ': ds) ('[] :: [Nat]) sh' Source # | |
Defined in Data.Array.Internal.Shape broadcasting' :: [Bool] Source # | |
(TypeError ('Text "Too few result dimensions") :: Constraint) => Broadcast' i (d ': ds) (s ': sh) ('[] :: [Nat]) Source # | |
Defined in Data.Array.Internal.Shape broadcasting' :: [Bool] Source # | |
Broadcast'' (CmpNat i d) i d ds (s ': sh) (s' ': sh') => Broadcast' i (d ': ds) (s ': sh) (s' ': sh') Source # | |
Defined in Data.Array.Internal.Shape broadcasting' :: [Bool] Source # |
class Broadcast (ds :: [Nat]) (sh :: [Nat]) (sh' :: [Nat]) where Source #
Using the dimension indices ds, can sh be broadcast into shape sh'?
broadcasting :: [Bool] Source #
Instances
Broadcast' 0 ds sh sh' => Broadcast ds sh sh' Source # | |
Defined in Data.Array.Internal.Shape broadcasting :: [Bool] Source # |
class Slice (ls :: [(Nat, Nat)]) (ss :: [Nat]) (rs :: [Nat]) | ls ss -> rs where Source #
class Stride (ts :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ts ss -> rs Source #
Instances
Stride ('[] :: [Nat]) ss ss Source # | |
Defined in Data.Array.Internal.Shape | |
(Stride ts ss rs, DivRoundUp s t ~ r) => Stride (t ': ts) (s ': ss) (r ': rs) Source # | |
Defined in Data.Array.Internal.Shape |
class Window (ws :: [Nat]) (ss :: [Nat]) (rs :: [Nat]) | ws ss -> rs Source #
Instances
Window' ws ws ss rs => Window ws ss rs Source # | |
Defined in Data.Array.Internal.Shape |
type Permute (is :: [Nat]) (xs :: [Nat]) = Permute' is (Take (Rank is) xs) ++ Drop (Rank is) xs Source #
class Permutation (is :: [Nat]) Source #
Instances
AllElem is (Count 0 is) => Permutation is Source # | |
Defined in Data.Array.Internal.Shape |
class Padded (ps :: [(Nat, Nat)]) (sh :: [Nat]) (sh' :: [Nat]) | ps sh -> sh' where Source #
class ValidStretch (from :: [Nat]) (to :: [Nat]) where Source #
Instances
ValidStretch ('[] :: [Nat]) ('[] :: [Nat]) Source # | |
Defined in Data.Array.Internal.Shape | |
(BoolVal (Stretch s m), ValidStretch ss ms) => ValidStretch (s ': ss) (m ': ms) Source # | |
Defined in Data.Array.Internal.Shape |
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.