Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Array.Nested.Mixed.Shape
Synopsis
- type family Rank (sh :: [a]) :: Natural where ...
- data ListX (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) where
- data UnconsListXRes (f :: Maybe Nat -> Type) (sh1 :: [Maybe Nat]) = (n ': sh) ~ sh1 => UnconsListXRes (ListX sh f) (f n)
- listxUncons :: forall (sh1 :: [Maybe Nat]) (f :: Maybe Nat -> Type). ListX sh1 f -> Maybe (UnconsListXRes f sh1)
- listxEqType :: forall (f :: Maybe Nat -> Type) (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). TestEquality f => ListX sh f -> ListX sh' f -> Maybe (sh :~: sh')
- listxEqual :: forall (f :: Maybe Nat -> Type) (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). (TestEquality f, forall (n :: Maybe Nat). Eq (f n)) => ListX sh f -> ListX sh' f -> Maybe (sh :~: sh')
- listxFmap :: forall f g (sh :: [Maybe Nat]). (forall (n :: Maybe Nat). f n -> g n) -> ListX sh f -> ListX sh g
- listxFold :: forall m f (sh :: [Maybe Nat]). Monoid m => (forall (n :: Maybe Nat). f n -> m) -> ListX sh f -> m
- listxLength :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type). ListX sh f -> Int
- listxRank :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type). ListX sh f -> SNat (Rank sh)
- listxShow :: forall (sh :: [Maybe Nat]) f. (forall (n :: Maybe Nat). f n -> ShowS) -> ListX sh f -> ShowS
- listxFromList :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> [i] -> ListX sh (Const i :: Maybe Nat -> Type)
- listxToList :: forall (sh' :: [Maybe Nat]) i. ListX sh' (Const i :: Maybe Nat -> Type) -> [i]
- listxHead :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) f. ListX (mn ': sh) f -> f mn
- listxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) (i :: Maybe Nat -> Type). ListX (n ': sh) i -> ListX sh i
- listxAppend :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) (sh' :: [Maybe Nat]). ListX sh f -> ListX sh' f -> ListX (sh ++ sh') f
- listxDrop :: forall (f :: Maybe Nat -> Type) (g :: Maybe Nat -> Type) (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). ListX sh g -> ListX (sh ++ sh') f -> ListX sh' f
- listxInit :: forall (f :: Maybe Nat -> Type) (n :: Maybe Nat) (sh :: [Maybe Nat]). ListX (n ': sh) f -> ListX (Init (n ': sh)) f
- listxLast :: forall f (n :: Maybe Nat) (sh :: [Maybe Nat]). ListX (n ': sh) f -> f (Last (n ': sh))
- listxZip :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) (g :: Maybe Nat -> Type). ListX sh f -> ListX sh g -> ListX sh (Product f g)
- listxZipWith :: forall f g h (sh :: [Maybe Nat]). (forall (a :: Maybe Nat). f a -> g a -> h a) -> ListX sh f -> ListX sh g -> ListX sh h
- newtype IxX (sh :: [Maybe Nat]) i = IxX (ListX sh (Const i :: Maybe Nat -> Type))
- pattern ZIX :: () => sh ~ ('[] :: [Maybe Nat]) => IxX sh i
- pattern (:.%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => forall. (n ': sh) ~ sh1 => i -> IxX sh i -> IxX sh1 i
- type IIxX (sh :: [Maybe Nat]) = IxX sh Int
- ixxLength :: forall (sh :: [Maybe Nat]) i. IxX sh i -> Int
- ixxRank :: forall (sh :: [Maybe Nat]) i. IxX sh i -> SNat (Rank sh)
- ixxZero :: forall (sh :: [Maybe Nat]). StaticShX sh -> IIxX sh
- ixxZero' :: forall (sh :: [Maybe Nat]). IShX sh -> IIxX sh
- ixxFromList :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> [i] -> IxX sh i
- ixxHead :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> i
- ixxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> IxX sh i
- ixxAppend :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. IxX sh i -> IxX sh' i -> IxX (sh ++ sh') i
- ixxDrop :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. IxX sh i -> IxX (sh ++ sh') i -> IxX sh' i
- ixxInit :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> IxX (Init (n ': sh)) i
- ixxLast :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> i
- ixxCast :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]) i. StaticShX sh' -> IxX sh i -> IxX sh' i
- ixxZip :: forall (sh :: [Maybe Nat]) i j. IxX sh i -> IxX sh j -> IxX sh (i, j)
- ixxZipWith :: forall i j k (sh :: [Maybe Nat]). (i -> j -> k) -> IxX sh i -> IxX sh j -> IxX sh k
- ixxFromLinear :: forall (sh :: [Maybe Nat]). IShX sh -> Int -> IIxX sh
- ixxToLinear :: forall (sh :: [Maybe Nat]). IShX sh -> IIxX sh -> Int
- data SMayNat i (f :: k -> Type) (n :: Maybe k) where
- fromSMayNat :: forall {k} (n :: Maybe k) i r f. (n ~ ('Nothing :: Maybe k) => i -> r) -> (forall (m :: k). n ~ 'Just m => f m -> r) -> SMayNat i f n -> r
- fromSMayNat' :: forall (n :: Maybe Nat). SMayNat Int SNat n -> Int
- type family AddMaybe (n :: Maybe Natural) (m :: Maybe Natural) :: Maybe Natural where ...
- smnAddMaybe :: forall (n :: Maybe Nat) (m :: Maybe Nat). SMayNat Int SNat n -> SMayNat Int SNat m -> SMayNat Int SNat (AddMaybe n m)
- newtype ShX (sh :: [Maybe Nat]) i = ShX (ListX sh (SMayNat i SNat))
- pattern ZSX :: () => sh ~ ('[] :: [Maybe Nat]) => ShX sh i
- pattern (:$%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat i SNat n -> ShX sh i -> ShX sh1 i
- type IShX (sh :: [Maybe Nat]) = ShX sh Int
- shxEqType :: forall (sh :: [Maybe Nat]) i (sh' :: [Maybe Nat]). ShX sh i -> ShX sh' i -> Maybe (sh :~: sh')
- shxEqual :: forall i (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Eq i => ShX sh i -> ShX sh' i -> Maybe (sh :~: sh')
- shxLength :: forall (sh :: [Maybe Nat]) i. ShX sh i -> Int
- shxRank :: forall (sh :: [Maybe Nat]) i. ShX sh i -> SNat (Rank sh)
- shxSize :: forall (sh :: [Maybe Nat]). IShX sh -> Int
- shxFromList :: forall (sh :: [Maybe Nat]). StaticShX sh -> [Int] -> IShX sh
- shxToList :: forall (sh :: [Maybe Nat]). IShX sh -> [Int]
- shxFromSSX :: forall (sh :: [Nat]) i. StaticShX (MapJust sh) -> ShX (MapJust sh) i
- shxFromSSX2 :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> Maybe (ShX sh i)
- shxAppend :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. ShX sh i -> ShX sh' i -> ShX (sh ++ sh') i
- shxHead :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> SMayNat i SNat n
- shxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> ShX sh i
- shxDropSSX :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. StaticShX sh -> ShX (sh ++ sh') i -> ShX sh' i
- shxDropIx :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i j. IxX sh j -> ShX (sh ++ sh') i -> ShX sh' i
- shxDropSh :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. ShX sh i -> ShX (sh ++ sh') i -> ShX sh' i
- shxInit :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> ShX (Init (n ': sh)) i
- shxLast :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> SMayNat i SNat (Last (n ': sh))
- shxTakeSSX :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i proxy. proxy sh' -> StaticShX sh -> ShX (sh ++ sh') i -> ShX sh i
- shxZipWith :: forall i j k (sh :: [Maybe Nat]). (forall (n :: Maybe Nat). SMayNat i SNat n -> SMayNat j SNat n -> SMayNat k SNat n) -> ShX sh i -> ShX sh j -> ShX sh k
- shxCompleteZeros :: forall (sh :: [Maybe Nat]). StaticShX sh -> IShX sh
- shxSplitApp :: forall proxy (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]) i. proxy sh' -> StaticShX sh -> ShX (sh ++ sh') i -> (ShX sh i, ShX sh' i)
- shxEnum :: forall (sh :: [Maybe Nat]). IShX sh -> [IIxX sh]
- shxCast :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]). StaticShX sh' -> IShX sh -> Maybe (IShX sh')
- shxCast' :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]). StaticShX sh' -> IShX sh -> IShX sh'
- newtype StaticShX (sh :: [Maybe Nat]) = StaticShX (ListX sh (SMayNat () SNat))
- pattern ZKX :: () => sh ~ ('[] :: [Maybe Nat]) => StaticShX sh
- pattern (:!%) :: forall {sh1} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat () SNat n -> StaticShX sh -> StaticShX sh1
- ssxLength :: forall (sh :: [Maybe Nat]). StaticShX sh -> Int
- ssxRank :: forall (sh :: [Maybe Nat]). StaticShX sh -> SNat (Rank sh)
- ssxEqType :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX sh' -> Maybe (sh :~: sh')
- ssxAppend :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX sh' -> StaticShX (sh ++ sh')
- ssxHead :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> SMayNat () SNat n
- ssxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> StaticShX sh
- ssxDropSSX :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX (sh ++ sh') -> StaticShX sh'
- ssxDropIx :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. IxX sh i -> StaticShX (sh ++ sh') -> StaticShX sh'
- ssxDropSh :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. ShX sh i -> StaticShX (sh ++ sh') -> StaticShX sh'
- ssxInit :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> StaticShX (Init (n ': sh))
- ssxLast :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> SMayNat () SNat (Last (n ': sh))
- ssxReplicate :: forall (n :: Nat). SNat n -> StaticShX (Replicate n ('Nothing :: Maybe Nat))
- ssxIotaFrom :: forall (sh :: [Maybe Nat]). StaticShX sh -> Int -> [Int]
- ssxFromShX :: forall (sh :: [Maybe Nat]) i. ShX sh i -> StaticShX sh
- ssxFromSNat :: forall (n :: Nat). SNat n -> StaticShX (Replicate n ('Nothing :: Maybe Nat))
- class KnownShX (sh :: [Maybe Nat]) where
- withKnownShX :: forall (sh :: [Maybe Nat]) r. StaticShX sh -> (KnownShX sh => r) -> r
- type Flatten (sh :: [Maybe Natural]) = Flatten' 1 sh
- type family Flatten' (acc :: Natural) (sh :: [Maybe Natural]) :: Maybe Natural where ...
- ssxFlatten :: forall (sh :: [Maybe Nat]). StaticShX sh -> SMayNat () SNat (Flatten sh)
- shxFlatten :: forall (sh :: [Maybe Nat]). IShX sh -> SMayNat Int SNat (Flatten sh)
Documentation
type family Rank (sh :: [a]) :: Natural where ... Source #
The length of a type-level list. If the argument is a shape, then the result is the rank of that shape.
Mixed lists
data ListX (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) where Source #
Constructors
ZX :: forall (f :: Maybe Nat -> Type). ListX ('[] :: [Maybe Nat]) f | |
(::%) :: forall (f :: Maybe Nat -> Type) (n :: Maybe Nat) (sh1 :: [Maybe Nat]). f n -> ListX sh1 f -> ListX (n ': sh1) f infixr 3 |
Instances
KnownShX sh => IsList (ListX sh (Const i :: Maybe Nat -> Type)) Source # | Very untyped: only length is checked (at runtime). |
Defined in Data.Array.Nested.Mixed.Shape Methods fromList :: [Item (ListX sh (Const i :: Maybe Nat -> Type))] -> ListX sh (Const i :: Maybe Nat -> Type) # fromListN :: Int -> [Item (ListX sh (Const i :: Maybe Nat -> Type))] -> ListX sh (Const i :: Maybe Nat -> Type) # toList :: ListX sh (Const i :: Maybe Nat -> Type) -> [Item (ListX sh (Const i :: Maybe Nat -> Type))] # | |
(forall (n :: Maybe Nat). Show (f n)) => Show (ListX sh f) Source # | |
(forall (n :: Maybe Nat). NFData (f n)) => NFData (ListX sh f) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
(forall (n :: Maybe Nat). Eq (f n)) => Eq (ListX sh f) Source # | |
(forall (n :: Maybe Nat). Ord (f n)) => Ord (ListX sh f) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
type Item (ListX sh (Const i :: Maybe Nat -> Type)) Source # | |
data UnconsListXRes (f :: Maybe Nat -> Type) (sh1 :: [Maybe Nat]) Source #
Constructors
(n ': sh) ~ sh1 => UnconsListXRes (ListX sh f) (f n) |
listxUncons :: forall (sh1 :: [Maybe Nat]) (f :: Maybe Nat -> Type). ListX sh1 f -> Maybe (UnconsListXRes f sh1) Source #
listxEqType :: forall (f :: Maybe Nat -> Type) (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). TestEquality f => ListX sh f -> ListX sh' f -> Maybe (sh :~: sh') Source #
This checks only whether the types are equal; if the elements of the list
are not singletons, their values may still differ. This corresponds to
testEquality
, except on the penultimate type parameter.
listxEqual :: forall (f :: Maybe Nat -> Type) (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). (TestEquality f, forall (n :: Maybe Nat). Eq (f n)) => ListX sh f -> ListX sh' f -> Maybe (sh :~: sh') Source #
This checks whether the two lists actually contain equal values. This is
more than testEquality
, and corresponds to geq
from Data.GADT.Compare
in the some
package (except on the penultimate type parameter).
listxFmap :: forall f g (sh :: [Maybe Nat]). (forall (n :: Maybe Nat). f n -> g n) -> ListX sh f -> ListX sh g Source #
listxFold :: forall m f (sh :: [Maybe Nat]). Monoid m => (forall (n :: Maybe Nat). f n -> m) -> ListX sh f -> m Source #
listxRank :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type). ListX sh f -> SNat (Rank sh) Source #
listxShow :: forall (sh :: [Maybe Nat]) f. (forall (n :: Maybe Nat). f n -> ShowS) -> ListX sh f -> ShowS Source #
listxFromList :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> [i] -> ListX sh (Const i :: Maybe Nat -> Type) Source #
listxToList :: forall (sh' :: [Maybe Nat]) i. ListX sh' (Const i :: Maybe Nat -> Type) -> [i] Source #
listxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) (i :: Maybe Nat -> Type). ListX (n ': sh) i -> ListX sh i Source #
listxAppend :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) (sh' :: [Maybe Nat]). ListX sh f -> ListX sh' f -> ListX (sh ++ sh') f Source #
listxDrop :: forall (f :: Maybe Nat -> Type) (g :: Maybe Nat -> Type) (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). ListX sh g -> ListX (sh ++ sh') f -> ListX sh' f Source #
listxInit :: forall (f :: Maybe Nat -> Type) (n :: Maybe Nat) (sh :: [Maybe Nat]). ListX (n ': sh) f -> ListX (Init (n ': sh)) f Source #
listxLast :: forall f (n :: Maybe Nat) (sh :: [Maybe Nat]). ListX (n ': sh) f -> f (Last (n ': sh)) Source #
listxZip :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) (g :: Maybe Nat -> Type). ListX sh f -> ListX sh g -> ListX sh (Product f g) Source #
listxZipWith :: forall f g h (sh :: [Maybe Nat]). (forall (a :: Maybe Nat). f a -> g a -> h a) -> ListX sh f -> ListX sh g -> ListX sh h Source #
Mixed indices
newtype IxX (sh :: [Maybe Nat]) i Source #
An index into a mixed-typed array.
Instances
Foldable (IxX sh) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape Methods fold :: Monoid m => IxX sh m -> m # foldMap :: Monoid m => (a -> m) -> IxX sh a -> m # foldMap' :: Monoid m => (a -> m) -> IxX sh a -> m # foldr :: (a -> b -> b) -> b -> IxX sh a -> b # foldr' :: (a -> b -> b) -> b -> IxX sh a -> b # foldl :: (b -> a -> b) -> b -> IxX sh a -> b # foldl' :: (b -> a -> b) -> b -> IxX sh a -> b # foldr1 :: (a -> a -> a) -> IxX sh a -> a # foldl1 :: (a -> a -> a) -> IxX sh a -> a # elem :: Eq a => a -> IxX sh a -> Bool # maximum :: Ord a => IxX sh a -> a # minimum :: Ord a => IxX sh a -> a # | |||||
Functor (IxX sh) Source # | |||||
Generic (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape Associated Types
| |||||
KnownShX sh => IsList (IxX sh i) Source # | Very untyped: only length is checked (at runtime), index bounds are not checked. | ||||
Show i => Show (IxX sh i) Source # | |||||
NFData i => NFData (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
Eq i => Eq (IxX sh i) Source # | |||||
Ord i => Ord (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
type Rep (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape type Rep (IxX sh i) = D1 ('MetaData "IxX" "Data.Array.Nested.Mixed.Shape" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "IxX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListX sh (Const i :: Maybe Nat -> Type))))) | |||||
type Item (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape |
pattern (:.%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => forall. (n ': sh) ~ sh1 => i -> IxX sh i -> IxX sh1 i infixr 3 Source #
ixxAppend :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. IxX sh i -> IxX sh' i -> IxX (sh ++ sh') i Source #
ixxDrop :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. IxX sh i -> IxX (sh ++ sh') i -> IxX sh' i Source #
ixxInit :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> IxX (Init (n ': sh)) i Source #
ixxCast :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]) i. StaticShX sh' -> IxX sh i -> IxX sh' i Source #
ixxZipWith :: forall i j k (sh :: [Maybe Nat]). (i -> j -> k) -> IxX sh i -> IxX sh j -> IxX sh k Source #
Mixed shapes
data SMayNat i (f :: k -> Type) (n :: Maybe k) where Source #
Constructors
SUnknown :: forall {k} i (f :: k -> Type). i -> SMayNat i f ('Nothing :: Maybe k) | |
SKnown :: forall {k} (f :: k -> Type) (n1 :: k) i. f n1 -> SMayNat i f ('Just n1) |
Instances
TestEquality f => TestEquality (SMayNat i f :: Maybe k -> Type) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
(Show i, forall (m :: k). Show (f m)) => Show (SMayNat i f n) Source # | |
(NFData i, forall (m :: k). NFData (f m)) => NFData (SMayNat i f n) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
(Eq i, forall (m :: k). Eq (f m)) => Eq (SMayNat i f n) Source # | |
(Ord i, forall (m :: k). Ord (f m)) => Ord (SMayNat i f n) Source # | |
Defined in Data.Array.Nested.Mixed.Shape Methods compare :: SMayNat i f n -> SMayNat i f n -> Ordering # (<) :: SMayNat i f n -> SMayNat i f n -> Bool # (<=) :: SMayNat i f n -> SMayNat i f n -> Bool # (>) :: SMayNat i f n -> SMayNat i f n -> Bool # (>=) :: SMayNat i f n -> SMayNat i f n -> Bool # |
fromSMayNat :: forall {k} (n :: Maybe k) i r f. (n ~ ('Nothing :: Maybe k) => i -> r) -> (forall (m :: k). n ~ 'Just m => f m -> r) -> SMayNat i f n -> r Source #
smnAddMaybe :: forall (n :: Maybe Nat) (m :: Maybe Nat). SMayNat Int SNat n -> SMayNat Int SNat m -> SMayNat Int SNat (AddMaybe n m) Source #
newtype ShX (sh :: [Maybe Nat]) i Source #
This is a newtype over ListX
.
Instances
Functor (ShX sh) Source # | |||||
Generic (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape Associated Types
| |||||
KnownShX sh => IsList (ShX sh Int) Source # | Untyped: length and known dimensions are checked (at runtime). | ||||
Defined in Data.Array.Nested.Mixed.Shape Associated Types
| |||||
Show i => Show (ShX sh i) Source # | |||||
NFData i => NFData (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
Eq i => Eq (ShX sh i) Source # | |||||
Ord i => Ord (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
type Rep (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
type Item (ShX sh Int) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape |
pattern (:$%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat i SNat n -> ShX sh i -> ShX sh1 i infixr 3 Source #
shxEqType :: forall (sh :: [Maybe Nat]) i (sh' :: [Maybe Nat]). ShX sh i -> ShX sh' i -> Maybe (sh :~: sh') Source #
This checks only whether the types are equal; unknown dimensions might
still differ. This corresponds to testEquality
, except on the penultimate
type parameter.
shxEqual :: forall i (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Eq i => ShX sh i -> ShX sh' i -> Maybe (sh :~: sh') Source #
This checks whether all dimensions have the same value. This is more than
testEquality
, and corresponds to geq
from Data.GADT.Compare
in the
some
package (except on the penultimate type parameter).
shxSize :: forall (sh :: [Maybe Nat]). IShX sh -> Int Source #
The number of elements in an array described by this shape.
shxFromSSX2 :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> Maybe (ShX sh i) Source #
This may fail if sh
has Nothing
s in it.
shxAppend :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. ShX sh i -> ShX sh' i -> ShX (sh ++ sh') i Source #
shxHead :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> SMayNat i SNat n Source #
shxDropSSX :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. StaticShX sh -> ShX (sh ++ sh') i -> ShX sh' i Source #
shxDropIx :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i j. IxX sh j -> ShX (sh ++ sh') i -> ShX sh' i Source #
shxDropSh :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. ShX sh i -> ShX (sh ++ sh') i -> ShX sh' i Source #
shxInit :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> ShX (Init (n ': sh)) i Source #
shxLast :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> SMayNat i SNat (Last (n ': sh)) Source #
shxTakeSSX :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i proxy. proxy sh' -> StaticShX sh -> ShX (sh ++ sh') i -> ShX sh i Source #
shxZipWith :: forall i j k (sh :: [Maybe Nat]). (forall (n :: Maybe Nat). SMayNat i SNat n -> SMayNat j SNat n -> SMayNat k SNat n) -> ShX sh i -> ShX sh j -> ShX sh k Source #
shxSplitApp :: forall proxy (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]) i. proxy sh' -> StaticShX sh -> ShX (sh ++ sh') i -> (ShX sh i, ShX sh' i) Source #
shxCast :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]). StaticShX sh' -> IShX sh -> Maybe (IShX sh') Source #
shxCast' :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]). StaticShX sh' -> IShX sh -> IShX sh' Source #
Partial version of shxCast
.
Static mixed shapes
newtype StaticShX (sh :: [Maybe Nat]) Source #
The part of a shape that is statically known. (A newtype over ListX
.)
Instances
Show (StaticShX sh) Source # | |
NFData (StaticShX sh) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
Eq (StaticShX sh) Source # | |
Ord (StaticShX sh) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
TestEquality StaticShX Source # | |
pattern (:!%) :: forall {sh1} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat () SNat n -> StaticShX sh -> StaticShX sh1 infixr 3 Source #
ssxEqType :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX sh' -> Maybe (sh :~: sh') Source #
ssxEqType =
. Provided for consistency.testEquality
ssxAppend :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX sh' -> StaticShX (sh ++ sh') Source #
ssxHead :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> SMayNat () SNat n Source #
ssxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> StaticShX sh Source #
ssxDropSSX :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX (sh ++ sh') -> StaticShX sh' Source #
ssxDropIx :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. IxX sh i -> StaticShX (sh ++ sh') -> StaticShX sh' Source #
ssxDropSh :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) i. ShX sh i -> StaticShX (sh ++ sh') -> StaticShX sh' Source #
ssxInit :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> StaticShX (Init (n ': sh)) Source #
ssxLast :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). StaticShX (n ': sh) -> SMayNat () SNat (Last (n ': sh)) Source #
ssxReplicate :: forall (n :: Nat). SNat n -> StaticShX (Replicate n ('Nothing :: Maybe Nat)) Source #
ssxFromSNat :: forall (n :: Nat). SNat n -> StaticShX (Replicate n ('Nothing :: Maybe Nat)) Source #
class KnownShX (sh :: [Maybe Nat]) where Source #
Evidence for the static part of a shape. This pops up only when you are polymorphic in the element type of an array.