Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Array.Nested.Shaped.Shape
Synopsis
- data ListS (sh :: [Nat]) (f :: Nat -> Type) where
- data UnconsListSRes (f :: Nat -> Type) (sh1 :: [Nat]) = (KnownNat n, (n ': sh) ~ sh1) => UnconsListSRes (ListS sh f) (f n)
- listsUncons :: forall (sh1 :: [Nat]) (f :: Nat -> Type). ListS sh1 f -> Maybe (UnconsListSRes f sh1)
- listsEqType :: forall (f :: Nat -> Type) (sh :: [Nat]) (sh' :: [Nat]). TestEquality f => ListS sh f -> ListS sh' f -> Maybe (sh :~: sh')
- listsEqual :: forall (f :: Nat -> Type) (sh :: [Nat]) (sh' :: [Nat]). (TestEquality f, forall (n :: Nat). Eq (f n)) => ListS sh f -> ListS sh' f -> Maybe (sh :~: sh')
- listsFmap :: forall f g (sh :: [Nat]). (forall (n :: Nat). f n -> g n) -> ListS sh f -> ListS sh g
- listsFold :: forall m f (sh :: [Nat]). Monoid m => (forall (n :: Nat). f n -> m) -> ListS sh f -> m
- listsShow :: forall (sh :: [Nat]) f. (forall (n :: Nat). f n -> ShowS) -> ListS sh f -> ShowS
- listsLength :: forall (sh :: [Nat]) (f :: Nat -> Type). ListS sh f -> Int
- listsRank :: forall (sh :: [Nat]) (f :: Nat -> Type). ListS sh f -> SNat (Rank sh)
- listsToList :: forall (sh :: [Nat]) i. ListS sh (Const i :: Nat -> Type) -> [i]
- listsHead :: forall (n :: Nat) (sh :: [Nat]) f. ListS (n ': sh) f -> f n
- listsTail :: forall (n :: Nat) (sh :: [Nat]) (f :: Nat -> Type). ListS (n ': sh) f -> ListS sh f
- listsInit :: forall (n :: Nat) (sh :: [Nat]) (f :: Nat -> Type). ListS (n ': sh) f -> ListS (Init (n ': sh)) f
- listsLast :: forall (n :: Nat) (sh :: [Nat]) f. ListS (n ': sh) f -> f (Last (n ': sh))
- listsAppend :: forall (sh :: [Nat]) (f :: Nat -> Type) (sh' :: [Nat]). ListS sh f -> ListS sh' f -> ListS (sh ++ sh') f
- listsZip :: forall (sh :: [Nat]) (f :: Nat -> Type) (g :: Nat -> Type). ListS sh f -> ListS sh g -> ListS sh (Product f g)
- listsZipWith :: forall f g h (sh :: [Nat]). (forall (a :: Nat). f a -> g a -> h a) -> ListS sh f -> ListS sh g -> ListS sh h
- listsTakeLenPerm :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (TakeLen is sh) f
- listsDropLenPerm :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (DropLen is sh) f
- listsPermute :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (Permute is sh) f
- listsIndex :: forall {k1} {k2} f (i :: Nat) (is :: k1) (sh :: [Nat]) (shT :: k2). Proxy is -> Proxy shT -> SNat i -> ListS sh f -> (f (Index i sh), SNat (Index i sh))
- listsPermutePrefix :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (PermutePrefix is sh) f
- newtype IxS (sh :: [Nat]) i = IxS (ListS sh (Const i :: Nat -> Type))
- pattern ZIS :: () => sh ~ ('[] :: [Nat]) => IxS sh i
- pattern (:.$) :: forall {sh1} {i} (n :: Nat) sh. () => forall. (KnownNat n, (n ': sh) ~ sh1) => i -> IxS sh i -> IxS sh1 i
- type IIxS (sh :: [Nat]) = IxS sh Int
- ixsLength :: forall (sh :: [Nat]) i. IxS sh i -> Int
- ixsRank :: forall (sh :: [Nat]) i. IxS sh i -> SNat (Rank sh)
- ixsZero :: forall (sh :: [Nat]). ShS sh -> IIxS sh
- ixsHead :: forall (n :: Nat) (sh :: [Nat]) i. IxS (n ': sh) i -> i
- ixsTail :: forall (n :: Nat) (sh :: [Nat]) i. IxS (n ': sh) i -> IxS sh i
- ixsInit :: forall (n :: Nat) (sh :: [Nat]) i. IxS (n ': sh) i -> IxS (Init (n ': sh)) i
- ixsLast :: forall (n :: Nat) (sh :: [Nat]) i. IxS (n ': sh) i -> i
- ixsCast :: forall (sh' :: [Nat]) (sh :: [Nat]) i. ShS sh' -> IxS sh i -> IxS sh' i
- ixsAppend :: forall (sh :: [Nat]) (sh' :: [Nat]) i. IxS sh i -> IxS sh' i -> IxS (sh ++ sh') i
- ixsZip :: forall (n :: [Nat]) i j. IxS n i -> IxS n j -> IxS n (i, j)
- ixsZipWith :: forall i j k (n :: [Nat]). (i -> j -> k) -> IxS n i -> IxS n j -> IxS n k
- ixsPermutePrefix :: forall i (is :: [Nat]) (sh :: [Nat]). Perm is -> IxS sh i -> IxS (PermutePrefix is sh) i
- newtype ShS (sh :: [Nat]) = ShS (ListS sh SNat)
- pattern ZSS :: () => sh ~ ('[] :: [Nat]) => ShS sh
- pattern (:$$) :: forall {sh1} (n :: Nat) sh. () => (KnownNat n, (n ': sh) ~ sh1) => SNat n -> ShS sh -> ShS sh1
- shsEqual :: forall (sh :: [Nat]) (sh' :: [Nat]). ShS sh -> ShS sh' -> Maybe (sh :~: sh')
- shsLength :: forall (sh :: [Nat]). ShS sh -> Int
- shsRank :: forall (sh :: [Nat]). ShS sh -> SNat (Rank sh)
- shsSize :: forall (sh :: [Nat]). ShS sh -> Int
- shsToList :: forall (sh :: [Nat]). ShS sh -> [Int]
- shsHead :: forall (n :: Nat) (sh :: [Nat]). ShS (n ': sh) -> SNat n
- shsTail :: forall (n :: Nat) (sh :: [Nat]). ShS (n ': sh) -> ShS sh
- shsInit :: forall (n :: Nat) (sh :: [Nat]). ShS (n ': sh) -> ShS (Init (n ': sh))
- shsLast :: forall (n :: Nat) (sh :: [Nat]). ShS (n ': sh) -> SNat (Last (n ': sh))
- shsAppend :: forall (sh :: [Nat]) (sh' :: [Nat]). ShS sh -> ShS sh' -> ShS (sh ++ sh')
- shsTakeLen :: forall (is :: [Nat]) (sh :: [Nat]). Perm is -> ShS sh -> ShS (TakeLen is sh)
- shsPermute :: forall (is :: [Nat]) (sh :: [Nat]). Perm is -> ShS sh -> ShS (Permute is sh)
- shsIndex :: forall {k1} {k2} (is :: k1) (shT :: k2) (i :: Nat) (sh :: [Nat]). Proxy is -> Proxy shT -> SNat i -> ShS sh -> SNat (Index i sh)
- shsPermutePrefix :: forall (is :: [Nat]) (sh :: [Nat]). Perm is -> ShS sh -> ShS (PermutePrefix is sh)
- type family Product (sh :: [Natural]) :: Natural where ...
- shsProduct :: forall (sh :: [Nat]). ShS sh -> SNat (Product sh)
- class KnownShS (sh :: [Nat]) where
- withKnownShS :: forall (sh :: [Nat]) r. ShS sh -> (KnownShS sh => r) -> r
- shsKnownShS :: forall (sh :: [Nat]). ShS sh -> Dict KnownShS sh
- shsOrthotopeShape :: forall (sh :: [Nat]). ShS sh -> Dict Shape sh
- shsFromListS :: forall (sh :: [Nat]) (f :: Nat -> Type). ListS sh f -> ShS sh
- shsFromIxS :: forall (sh :: [Nat]) i. IxS sh i -> ShS sh
Shaped lists
data ListS (sh :: [Nat]) (f :: Nat -> Type) where Source #
Constructors
ZS :: forall (f :: Nat -> Type). ListS ('[] :: [Nat]) f | |
(::$) :: forall (n :: Nat) (sh1 :: [Nat]) {f :: Nat -> Type}. KnownNat n => f n -> ListS sh1 f -> ListS (n ': sh1) f infixr 3 |
Instances
KnownShS sh => IsList (ListS sh (Const i :: Nat -> Type)) Source # | Untyped: length is checked at runtime. |
(forall (n :: Nat). Show (f n)) => Show (ListS sh f) Source # | |
(forall (m :: Nat). NFData (f m)) => NFData (ListS n f) Source # | |
Defined in Data.Array.Nested.Shaped.Shape | |
(forall (n :: Nat). Eq (f n)) => Eq (ListS sh f) Source # | |
(forall (n :: Nat). Ord (f n)) => Ord (ListS sh f) Source # | |
Defined in Data.Array.Nested.Shaped.Shape | |
type Item (ListS sh (Const i :: Nat -> Type)) Source # | |
data UnconsListSRes (f :: Nat -> Type) (sh1 :: [Nat]) Source #
Constructors
(KnownNat n, (n ': sh) ~ sh1) => UnconsListSRes (ListS sh f) (f n) |
listsUncons :: forall (sh1 :: [Nat]) (f :: Nat -> Type). ListS sh1 f -> Maybe (UnconsListSRes f sh1) Source #
listsEqType :: forall (f :: Nat -> Type) (sh :: [Nat]) (sh' :: [Nat]). TestEquality f => ListS sh f -> ListS 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.
listsEqual :: forall (f :: Nat -> Type) (sh :: [Nat]) (sh' :: [Nat]). (TestEquality f, forall (n :: Nat). Eq (f n)) => ListS sh f -> ListS 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).
listsFmap :: forall f g (sh :: [Nat]). (forall (n :: Nat). f n -> g n) -> ListS sh f -> ListS sh g Source #
listsFold :: forall m f (sh :: [Nat]). Monoid m => (forall (n :: Nat). f n -> m) -> ListS sh f -> m Source #
listsShow :: forall (sh :: [Nat]) f. (forall (n :: Nat). f n -> ShowS) -> ListS sh f -> ShowS Source #
listsTail :: forall (n :: Nat) (sh :: [Nat]) (f :: Nat -> Type). ListS (n ': sh) f -> ListS sh f Source #
listsInit :: forall (n :: Nat) (sh :: [Nat]) (f :: Nat -> Type). ListS (n ': sh) f -> ListS (Init (n ': sh)) f Source #
listsAppend :: forall (sh :: [Nat]) (f :: Nat -> Type) (sh' :: [Nat]). ListS sh f -> ListS sh' f -> ListS (sh ++ sh') f Source #
listsZip :: forall (sh :: [Nat]) (f :: Nat -> Type) (g :: Nat -> Type). ListS sh f -> ListS sh g -> ListS sh (Product f g) Source #
listsZipWith :: forall f g h (sh :: [Nat]). (forall (a :: Nat). f a -> g a -> h a) -> ListS sh f -> ListS sh g -> ListS sh h Source #
listsTakeLenPerm :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (TakeLen is sh) f Source #
listsDropLenPerm :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (DropLen is sh) f Source #
listsPermute :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (Permute is sh) f Source #
listsIndex :: forall {k1} {k2} f (i :: Nat) (is :: k1) (sh :: [Nat]) (shT :: k2). Proxy is -> Proxy shT -> SNat i -> ListS sh f -> (f (Index i sh), SNat (Index i sh)) Source #
listsPermutePrefix :: forall (f :: Nat -> Type) (is :: [Nat]) (sh :: [Nat]). Perm is -> ListS sh f -> ListS (PermutePrefix is sh) f Source #
Shaped indices
newtype IxS (sh :: [Nat]) i Source #
An index into a shape-typed array.
Instances
Foldable (IxS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape Methods fold :: Monoid m => IxS sh m -> m # foldMap :: Monoid m => (a -> m) -> IxS sh a -> m # foldMap' :: Monoid m => (a -> m) -> IxS sh a -> m # foldr :: (a -> b -> b) -> b -> IxS sh a -> b # foldr' :: (a -> b -> b) -> b -> IxS sh a -> b # foldl :: (b -> a -> b) -> b -> IxS sh a -> b # foldl' :: (b -> a -> b) -> b -> IxS sh a -> b # foldr1 :: (a -> a -> a) -> IxS sh a -> a # foldl1 :: (a -> a -> a) -> IxS sh a -> a # elem :: Eq a => a -> IxS sh a -> Bool # maximum :: Ord a => IxS sh a -> a # minimum :: Ord a => IxS sh a -> a # | |||||
Functor (IxS sh) Source # | |||||
Generic (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape Associated Types
| |||||
KnownShS sh => IsList (IxS sh i) Source # | Very untyped: only length is checked (at runtime), index bounds are not checked. | ||||
Show i => Show (IxS sh i) Source # | |||||
NFData i => NFData (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
Eq i => Eq (IxS sh i) Source # | |||||
Ord i => Ord (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
type Rep (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape type Rep (IxS sh i) = D1 ('MetaData "IxS" "Data.Array.Nested.Shaped.Shape" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "IxS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListS sh (Const i :: Nat -> Type))))) | |||||
type Item (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape |
pattern (:.$) :: forall {sh1} {i} (n :: Nat) sh. () => forall. (KnownNat n, (n ': sh) ~ sh1) => i -> IxS sh i -> IxS sh1 i infixr 3 Source #
ixsAppend :: forall (sh :: [Nat]) (sh' :: [Nat]) i. IxS sh i -> IxS sh' i -> IxS (sh ++ sh') i Source #
ixsPermutePrefix :: forall i (is :: [Nat]) (sh :: [Nat]). Perm is -> IxS sh i -> IxS (PermutePrefix is sh) i Source #
Shaped shapes
newtype ShS (sh :: [Nat]) Source #
The shape of a shape-typed array given as a list of SNat
values.
Note that because the shape of a shape-typed array is known statically, you
can also retrieve the array shape from a KnownShS
dictionary.
Instances
Generic (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape Associated Types
| |||||
KnownShS sh => IsList (ShS sh) Source # | Untyped: length and values are checked at runtime. | ||||
Show (ShS sh) Source # | |||||
NFData (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
Eq (ShS sh) Source # | |||||
Ord (ShS sh) Source # | |||||
TestEquality ShS Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
type Rep (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
type Item (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape |
pattern (:$$) :: forall {sh1} (n :: Nat) sh. () => (KnownNat n, (n ': sh) ~ sh1) => SNat n -> ShS sh -> ShS sh1 infixr 3 Source #
shsEqual :: forall (sh :: [Nat]) (sh' :: [Nat]). ShS sh -> ShS sh' -> Maybe (sh :~: sh') Source #
. (Because shsEqual
= testEquality
ShS
is a singleton, types are
equal if and only if values are equal.)
shsIndex :: forall {k1} {k2} (is :: k1) (shT :: k2) (i :: Nat) (sh :: [Nat]). Proxy is -> Proxy shT -> SNat i -> ShS sh -> SNat (Index i sh) Source #
shsPermutePrefix :: forall (is :: [Nat]) (sh :: [Nat]). Perm is -> ShS sh -> ShS (PermutePrefix is sh) Source #
class KnownShS (sh :: [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.