ox-arrays-0.1.0.0: An efficient CPU-based multidimensional array (tensor) library
Safe HaskellNone
LanguageHaskell2010

Data.Array.Nested.Mixed.Shape

Synopsis

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.

Equations

Rank ('[] :: [a]) = 0 
Rank (_1 ': sh :: [a]) = Rank sh + 1 

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

Instances details
KnownShX sh => IsList (ListX sh (Const i :: Maybe Nat -> Type)) Source #

Very untyped: only length is checked (at runtime).

Instance details

Defined in Data.Array.Nested.Mixed.Shape

Associated Types

type Item (ListX sh (Const i :: Maybe Nat -> Type)) 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Item (ListX sh (Const i :: Maybe Nat -> Type)) = i

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 # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

showsPrec :: Int -> ListX sh f -> ShowS #

show :: ListX sh f -> String #

showList :: [ListX sh f] -> ShowS #

(forall (n :: Maybe Nat). NFData (f n)) => NFData (ListX sh f) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

rnf :: ListX sh f -> () #

(forall (n :: Maybe Nat). Eq (f n)) => Eq (ListX sh f) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

(==) :: ListX sh f -> ListX sh f -> Bool #

(/=) :: ListX sh f -> ListX sh f -> Bool #

(forall (n :: Maybe Nat). Ord (f n)) => Ord (ListX sh f) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

compare :: ListX sh f -> ListX sh f -> Ordering #

(<) :: ListX sh f -> ListX sh f -> Bool #

(<=) :: ListX sh f -> ListX sh f -> Bool #

(>) :: ListX sh f -> ListX sh f -> Bool #

(>=) :: ListX sh f -> ListX sh f -> Bool #

max :: ListX sh f -> ListX sh f -> ListX sh f #

min :: ListX sh f -> ListX sh f -> ListX sh f #

type Item (ListX sh (Const i :: Maybe Nat -> Type)) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Item (ListX sh (Const i :: Maybe Nat -> Type)) = i

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 #

listxLength :: forall (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type). ListX sh f -> Int 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 #

listxHead :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) f. ListX (mn ': sh) f -> f mn 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.

Constructors

IxX (ListX sh (Const i :: Maybe Nat -> Type)) 

Instances

Instances details
Foldable (IxX sh) Source # 
Instance details

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 #

toList :: IxX sh a -> [a] #

null :: IxX sh a -> Bool #

length :: IxX sh a -> Int #

elem :: Eq a => a -> IxX sh a -> Bool #

maximum :: Ord a => IxX sh a -> a #

minimum :: Ord a => IxX sh a -> a #

sum :: Num a => IxX sh a -> a #

product :: Num a => IxX sh a -> a #

Functor (IxX sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

fmap :: (a -> b) -> IxX sh a -> IxX sh b #

(<$) :: a -> IxX sh b -> IxX sh a #

Generic (IxX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Associated Types

type Rep (IxX sh i) 
Instance details

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)))))

Methods

from :: IxX sh i -> Rep (IxX sh i) x #

to :: Rep (IxX sh i) x -> IxX sh i #

KnownShX sh => IsList (IxX sh i) Source #

Very untyped: only length is checked (at runtime), index bounds are not checked.

Instance details

Defined in Data.Array.Nested.Mixed.Shape

Associated Types

type Item (IxX sh i) 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Item (IxX sh i) = i

Methods

fromList :: [Item (IxX sh i)] -> IxX sh i #

fromListN :: Int -> [Item (IxX sh i)] -> IxX sh i #

toList :: IxX sh i -> [Item (IxX sh i)] #

Show i => Show (IxX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

showsPrec :: Int -> IxX sh i -> ShowS #

show :: IxX sh i -> String #

showList :: [IxX sh i] -> ShowS #

NFData i => NFData (IxX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

rnf :: IxX sh i -> () #

Eq i => Eq (IxX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

(==) :: IxX sh i -> IxX sh i -> Bool #

(/=) :: IxX sh i -> IxX sh i -> Bool #

Ord i => Ord (IxX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

compare :: IxX sh i -> IxX sh i -> Ordering #

(<) :: IxX sh i -> IxX sh i -> Bool #

(<=) :: IxX sh i -> IxX sh i -> Bool #

(>) :: IxX sh i -> IxX sh i -> Bool #

(>=) :: IxX sh i -> IxX sh i -> Bool #

max :: IxX sh i -> IxX sh i -> IxX sh i #

min :: IxX sh i -> IxX sh i -> IxX sh i #

type Rep (IxX sh i) Source # 
Instance details

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 # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Item (IxX sh i) = i

pattern ZIX :: () => sh ~ ('[] :: [Maybe Nat]) => IxX sh i Source #

pattern (:.%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => forall. (n ': sh) ~ sh1 => i -> IxX sh i -> IxX sh1 i infixr 3 Source #

type IIxX (sh :: [Maybe Nat]) = IxX sh Int Source #

ixxLength :: forall (sh :: [Maybe Nat]) i. IxX sh i -> Int Source #

ixxRank :: forall (sh :: [Maybe Nat]) i. IxX sh i -> SNat (Rank sh) Source #

ixxZero :: forall (sh :: [Maybe Nat]). StaticShX sh -> IIxX sh Source #

ixxZero' :: forall (sh :: [Maybe Nat]). IShX sh -> IIxX sh Source #

ixxFromList :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> [i] -> IxX sh i Source #

ixxHead :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> i Source #

ixxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> IxX sh i 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 #

ixxLast :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. IxX (n ': sh) i -> i Source #

ixxCast :: forall (sh' :: [Maybe Nat]) (sh :: [Maybe Nat]) i. StaticShX sh' -> IxX sh i -> IxX sh' i Source #

ixxZip :: forall (sh :: [Maybe Nat]) i j. IxX sh i -> IxX sh j -> IxX sh (i, j) Source #

ixxZipWith :: forall i j k (sh :: [Maybe Nat]). (i -> j -> k) -> IxX sh i -> IxX sh j -> IxX sh k Source #

ixxFromLinear :: forall (sh :: [Maybe Nat]). IShX sh -> Int -> IIxX sh Source #

ixxToLinear :: forall (sh :: [Maybe Nat]). IShX sh -> IIxX sh -> Int 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

Instances details
TestEquality f => TestEquality (SMayNat i f :: Maybe k -> Type) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

testEquality :: forall (a :: Maybe k) (b :: Maybe k). SMayNat i f a -> SMayNat i f b -> Maybe (a :~: b) #

(Show i, forall (m :: k). Show (f m)) => Show (SMayNat i f n) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

showsPrec :: Int -> SMayNat i f n -> ShowS #

show :: SMayNat i f n -> String #

showList :: [SMayNat i f n] -> ShowS #

(NFData i, forall (m :: k). NFData (f m)) => NFData (SMayNat i f n) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

rnf :: SMayNat i f n -> () #

(Eq i, forall (m :: k). Eq (f m)) => Eq (SMayNat i f n) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

(==) :: SMayNat i f n -> SMayNat i f n -> Bool #

(/=) :: SMayNat i f n -> SMayNat i f n -> Bool #

(Ord i, forall (m :: k). Ord (f m)) => Ord (SMayNat i f n) Source # 
Instance details

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 #

max :: SMayNat i f n -> SMayNat i f n -> SMayNat i f n #

min :: SMayNat i f n -> SMayNat i f n -> SMayNat i f n #

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 #

fromSMayNat' :: forall (n :: Maybe Nat). SMayNat Int SNat n -> Int Source #

type family AddMaybe (n :: Maybe Natural) (m :: Maybe Natural) :: Maybe Natural where ... Source #

Equations

AddMaybe ('Nothing :: Maybe Natural) _1 = 'Nothing :: Maybe Natural 
AddMaybe ('Just _1) ('Nothing :: Maybe Natural) = 'Nothing :: Maybe Natural 
AddMaybe ('Just n) ('Just m) = 'Just (n + m) 

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.

Constructors

ShX (ListX sh (SMayNat i SNat)) 

Instances

Instances details
Functor (ShX sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

fmap :: (a -> b) -> ShX sh a -> ShX sh b #

(<$) :: a -> ShX sh b -> ShX sh a #

Generic (ShX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Associated Types

type Rep (ShX sh i) 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Rep (ShX sh i) = D1 ('MetaData "ShX" "Data.Array.Nested.Mixed.Shape" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "ShX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListX sh (SMayNat i SNat)))))

Methods

from :: ShX sh i -> Rep (ShX sh i) x #

to :: Rep (ShX sh i) x -> ShX sh i #

KnownShX sh => IsList (ShX sh Int) Source #

Untyped: length and known dimensions are checked (at runtime).

Instance details

Defined in Data.Array.Nested.Mixed.Shape

Associated Types

type Item (ShX sh Int) 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Item (ShX sh Int) = Int

Methods

fromList :: [Item (ShX sh Int)] -> ShX sh Int #

fromListN :: Int -> [Item (ShX sh Int)] -> ShX sh Int #

toList :: ShX sh Int -> [Item (ShX sh Int)] #

Show i => Show (ShX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

showsPrec :: Int -> ShX sh i -> ShowS #

show :: ShX sh i -> String #

showList :: [ShX sh i] -> ShowS #

NFData i => NFData (ShX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

rnf :: ShX sh i -> () #

Eq i => Eq (ShX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

(==) :: ShX sh i -> ShX sh i -> Bool #

(/=) :: ShX sh i -> ShX sh i -> Bool #

Ord i => Ord (ShX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

compare :: ShX sh i -> ShX sh i -> Ordering #

(<) :: ShX sh i -> ShX sh i -> Bool #

(<=) :: ShX sh i -> ShX sh i -> Bool #

(>) :: ShX sh i -> ShX sh i -> Bool #

(>=) :: ShX sh i -> ShX sh i -> Bool #

max :: ShX sh i -> ShX sh i -> ShX sh i #

min :: ShX sh i -> ShX sh i -> ShX sh i #

type Rep (ShX sh i) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Rep (ShX sh i) = D1 ('MetaData "ShX" "Data.Array.Nested.Mixed.Shape" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "ShX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListX sh (SMayNat i SNat)))))
type Item (ShX sh Int) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

type Item (ShX sh Int) = Int

pattern ZSX :: () => sh ~ ('[] :: [Maybe Nat]) => ShX sh i Source #

pattern (:$%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat i SNat n -> ShX sh i -> ShX sh1 i infixr 3 Source #

type IShX (sh :: [Maybe Nat]) = ShX sh Int 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).

shxLength :: forall (sh :: [Maybe Nat]) i. ShX sh i -> Int Source #

shxRank :: forall (sh :: [Maybe Nat]) i. ShX sh i -> SNat (Rank sh) Source #

shxSize :: forall (sh :: [Maybe Nat]). IShX sh -> Int Source #

The number of elements in an array described by this shape.

shxFromList :: forall (sh :: [Maybe Nat]). StaticShX sh -> [Int] -> IShX sh Source #

shxToList :: forall (sh :: [Maybe Nat]). IShX sh -> [Int] Source #

shxFromSSX :: forall (sh :: [Nat]) i. StaticShX (MapJust sh) -> ShX (MapJust sh) i Source #

shxFromSSX2 :: forall (sh :: [Maybe Nat]) i. StaticShX sh -> Maybe (ShX sh i) Source #

This may fail if sh has Nothings 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 #

shxTail :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]) i. ShX (n ': sh) i -> ShX sh i 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 #

shxCompleteZeros :: forall (sh :: [Maybe Nat]). StaticShX sh -> IShX sh 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 #

shxEnum :: forall (sh :: [Maybe Nat]). IShX sh -> [IIxX sh] 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.)

Constructors

StaticShX (ListX sh (SMayNat () SNat)) 

Instances

Instances details
Show (StaticShX sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

showsPrec :: Int -> StaticShX sh -> ShowS #

show :: StaticShX sh -> String #

showList :: [StaticShX sh] -> ShowS #

NFData (StaticShX sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

rnf :: StaticShX sh -> () #

Eq (StaticShX sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

(==) :: StaticShX sh -> StaticShX sh -> Bool #

(/=) :: StaticShX sh -> StaticShX sh -> Bool #

Ord (StaticShX sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

compare :: StaticShX sh -> StaticShX sh -> Ordering #

(<) :: StaticShX sh -> StaticShX sh -> Bool #

(<=) :: StaticShX sh -> StaticShX sh -> Bool #

(>) :: StaticShX sh -> StaticShX sh -> Bool #

(>=) :: StaticShX sh -> StaticShX sh -> Bool #

max :: StaticShX sh -> StaticShX sh -> StaticShX sh #

min :: StaticShX sh -> StaticShX sh -> StaticShX sh #

TestEquality StaticShX Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

testEquality :: forall (a :: [Maybe Nat]) (b :: [Maybe Nat]). StaticShX a -> StaticShX b -> Maybe (a :~: b) #

pattern ZKX :: () => sh ~ ('[] :: [Maybe Nat]) => StaticShX sh Source #

pattern (:!%) :: forall {sh1} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat () SNat n -> StaticShX sh -> StaticShX sh1 infixr 3 Source #

ssxLength :: forall (sh :: [Maybe Nat]). StaticShX sh -> Int Source #

ssxRank :: forall (sh :: [Maybe Nat]). StaticShX sh -> SNat (Rank sh) Source #

ssxEqType :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). StaticShX sh -> StaticShX sh' -> Maybe (sh :~: sh') Source #

ssxEqType = testEquality. Provided for consistency.

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 #

ssxIotaFrom :: forall (sh :: [Maybe Nat]). StaticShX sh -> Int -> [Int] Source #

ssxFromShX :: forall (sh :: [Maybe Nat]) i. ShX sh i -> StaticShX sh 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.

Methods

knownShX :: StaticShX sh Source #

Instances

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

Defined in Data.Array.Nested.Mixed.Shape

Methods

knownShX :: StaticShX ('[] :: [Maybe Nat]) Source #

(KnownNat n, KnownShX sh) => KnownShX ('Just n ': sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

knownShX :: StaticShX ('Just n ': sh) Source #

KnownShX sh => KnownShX (('Nothing :: Maybe Nat) ': sh) Source # 
Instance details

Defined in Data.Array.Nested.Mixed.Shape

Methods

knownShX :: StaticShX (('Nothing :: Maybe Nat) ': sh) Source #

withKnownShX :: forall (sh :: [Maybe Nat]) r. StaticShX sh -> (KnownShX sh => r) -> r Source #

Flattening

type Flatten (sh :: [Maybe Natural]) = Flatten' 1 sh Source #

type family Flatten' (acc :: Natural) (sh :: [Maybe Natural]) :: Maybe Natural where ... Source #

Equations

Flatten' acc ('[] :: [Maybe Natural]) = 'Just acc 
Flatten' acc (('Nothing :: Maybe Natural) ': sh) = 'Nothing :: Maybe Natural 
Flatten' acc ('Just n ': sh) = Flatten' (acc * n) sh 

ssxFlatten :: forall (sh :: [Maybe Nat]). StaticShX sh -> SMayNat () SNat (Flatten sh) Source #

shxFlatten :: forall (sh :: [Maybe Nat]). IShX sh -> SMayNat Int SNat (Flatten sh) Source #