Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Array.Nested.Mixed
Synopsis
- newtype Primitive a = Primitive a
- class (Storable a, Elt a) => PrimElt a where
- data family Mixed (sh :: [Maybe Nat]) a
- data family MixedVecs s (sh :: [Maybe Nat]) a
- showsMixedArray :: forall a (sh :: [Maybe Nat]). (Show a, Elt a) => String -> String -> Int -> Mixed sh a -> ShowS
- mliftNumElt1 :: forall a b (sh :: [Maybe Nat]). (PrimElt a, PrimElt b) => (SNat (Rank sh) -> Array (Rank sh) a -> Array (Rank sh) b) -> Mixed sh a -> Mixed sh b
- mliftNumElt2 :: forall a b c (sh :: [Maybe Nat]). (PrimElt a, PrimElt b, PrimElt c) => (SNat (Rank sh) -> Array (Rank sh) a -> Array (Rank sh) b -> Array (Rank sh) c) -> Mixed sh a -> Mixed sh b -> Mixed sh c
- mquotArray :: forall a (sh :: [Maybe Nat]). (IntElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a
- mremArray :: forall a (sh :: [Maybe Nat]). (IntElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a
- matan2Array :: forall a (sh :: [Maybe Nat]). (FloatElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a
- class Elt a where
- type ShapeTree a
- mshape :: forall (sh :: [Maybe Nat]). Mixed sh a -> IShX sh
- mindex :: forall (sh :: [Maybe Nat]). Mixed sh a -> IIxX sh -> a
- mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') a -> IIxX sh -> Mixed sh' a
- mscalar :: a -> Mixed ('[] :: [Maybe Nat]) a
- mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh a) -> Mixed (('Nothing :: Maybe Nat) ': sh) a
- mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) a -> [Mixed sh a]
- mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 a -> Mixed sh2 a
- mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 a -> Mixed sh2 a -> Mixed sh3 a
- mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 a) -> NonEmpty (Mixed sh2 a)
- mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') a -> Mixed (sh2 ++ sh') a
- mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh a -> Mixed (PermutePrefix is sh) a
- mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) a) -> Mixed (('Nothing :: Maybe Nat) ': sh) a
- mrnf :: forall (sh :: [Maybe Nat]). Mixed sh a -> ()
- mshapeTree :: a -> ShapeTree a
- mshapeTreeEq :: Proxy a -> ShapeTree a -> ShapeTree a -> Bool
- mshapeTreeEmpty :: Proxy a -> ShapeTree a -> Bool
- mshowShapeTree :: Proxy a -> ShapeTree a -> String
- marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh a -> Bag [Int]
- mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> a -> MixedVecs s sh a -> ST s ()
- mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' a -> MixedVecs s (sh ++ sh') a -> ST s ()
- mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh a -> ST s (Mixed sh a)
- class Elt a => KnownElt a where
- memptyArray :: forall a (sh :: [Maybe Nat]). KnownElt a => IShX sh -> Mixed ('Just 0 ': sh) a
- mrank :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> SNat (Rank sh)
- msize :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> Int
- mgenerate :: forall (sh :: [Maybe Nat]) a. KnownElt a => IShX sh -> (IIxX sh -> a) -> Mixed sh a
- msumOuter1P :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (Storable a, NumElt a) => Mixed (n ': sh) (Primitive a) -> Mixed sh (Primitive a)
- msumOuter1 :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (NumElt a, PrimElt a) => Mixed (n ': sh) a -> Mixed sh a
- msumAllPrim :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> a
- mappend :: forall (n :: Maybe Nat) (m :: Maybe Nat) (sh :: [Maybe Nat]) a. Elt a => Mixed (n ': sh) a -> Mixed (m ': sh) a -> Mixed (AddMaybe n m ': sh) a
- mfromVectorP :: forall (sh :: [Maybe Nat]) a. Storable a => IShX sh -> Vector a -> Mixed sh (Primitive a)
- mfromVector :: forall (sh :: [Maybe Nat]) a. PrimElt a => IShX sh -> Vector a -> Mixed sh a
- mtoVectorP :: forall a (sh :: [Maybe Nat]). Storable a => Mixed sh (Primitive a) -> Vector a
- mtoVector :: forall a (sh :: [Maybe Nat]). PrimElt a => Mixed sh a -> Vector a
- mfromList1 :: Elt a => NonEmpty a -> Mixed '['Nothing :: Maybe Nat] a
- mfromListLinear :: forall (sh :: [Maybe Nat]) a. Elt a => IShX sh -> NonEmpty a -> Mixed sh a
- mfromListPrim :: PrimElt a => [a] -> Mixed '['Nothing :: Maybe Nat] a
- mfromListPrimLinear :: forall a (sh :: [Maybe Nat]). PrimElt a => IShX sh -> [a] -> Mixed sh a
- mtoList :: forall a (n :: Maybe Nat). Elt a => Mixed '[n] a -> [a]
- mtoListLinear :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> [a]
- munScalar :: Elt a => Mixed ('[] :: [Maybe Nat]) a -> a
- mnest :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Elt a => StaticShX sh -> Mixed (sh ++ sh') a -> Mixed sh (Mixed sh' a)
- munNest :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Mixed sh (Mixed sh' a) -> Mixed (sh ++ sh') a
- mzip :: forall a b (sh :: [Maybe Nat]). (Elt a, Elt b) => Mixed sh a -> Mixed sh b -> Mixed sh (a, b)
- munzip :: forall (sh :: [Maybe Nat]) a b. Mixed sh (a, b) -> (Mixed sh a, Mixed sh b)
- mrerankP :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh :: [Maybe Nat]) a b. (Storable a, Storable b) => StaticShX sh -> IShX sh2 -> (Mixed sh1 (Primitive a) -> Mixed sh2 (Primitive b)) -> Mixed (sh ++ sh1) (Primitive a) -> Mixed (sh ++ sh2) (Primitive b)
- mrerank :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh :: [Maybe Nat]) a b. (PrimElt a, PrimElt b) => StaticShX sh -> IShX sh2 -> (Mixed sh1 a -> Mixed sh2 b) -> Mixed (sh ++ sh1) a -> Mixed (sh ++ sh2) b
- mreplicate :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Elt a => IShX sh -> Mixed sh' a -> Mixed (sh ++ sh') a
- mreplicateScalP :: forall (sh :: [Maybe Nat]) a. Storable a => IShX sh -> a -> Mixed sh (Primitive a)
- mreplicateScal :: forall (sh :: [Maybe Nat]) a. PrimElt a => IShX sh -> a -> Mixed sh a
- mslice :: forall a (i :: Nat) (n :: Nat) (k :: Natural) (sh :: [Maybe Natural]). Elt a => SNat i -> SNat n -> Mixed ('Just ((i + n) + k) ': sh) a -> Mixed ('Just n ': sh) a
- msliceU :: forall a (sh :: [Maybe Nat]). Elt a => Int -> Int -> Mixed (('Nothing :: Maybe Nat) ': sh) a -> Mixed (('Nothing :: Maybe Nat) ': sh) a
- mrev1 :: forall a (n :: Maybe Nat) (sh :: [Maybe Nat]). Elt a => Mixed (n ': sh) a -> Mixed (n ': sh) a
- mreshape :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Elt a => IShX sh' -> Mixed sh a -> Mixed sh' a
- mflatten :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> Mixed '[Flatten sh] a
- miota :: forall a (n :: Nat). (Enum a, PrimElt a) => SNat n -> Mixed '['Just n] a
- mminIndexPrim :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> IIxX sh
- mmaxIndexPrim :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> IIxX sh
- mdot1Inner :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (PrimElt a, NumElt a) => Proxy n -> Mixed (sh ++ '[n]) a -> Mixed (sh ++ '[n]) a -> Mixed sh a
- mdot :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> Mixed sh a -> a
- mtoXArrayPrimP :: forall (sh :: [Maybe Nat]) a. Mixed sh (Primitive a) -> (IShX sh, XArray sh a)
- mtoXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => Mixed sh a -> (IShX sh, XArray sh a)
- mfromXArrayPrimP :: forall (sh :: [Maybe Nat]) a. StaticShX sh -> XArray sh a -> Mixed sh (Primitive a)
- mfromXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => StaticShX sh -> XArray sh a -> Mixed sh a
- mliftPrim :: forall a b (sh :: [Maybe Nat]). (PrimElt a, PrimElt b) => (a -> b) -> Mixed sh a -> Mixed sh b
- mliftPrim2 :: forall a b c (sh :: [Maybe Nat]). (PrimElt a, PrimElt b, PrimElt c) => (a -> b -> c) -> Mixed sh a -> Mixed sh b -> Mixed sh c
Documentation
Wrapper type used as a tag to attach instances on. The instances on arrays
of
are more polymorphic than the direct instances for arrays
of scalars; this means that if Primitive
aorthotope
supports an element type T
that
this library does not (directly), it may just work if you use an array of
instead.Primitive
T
Constructors
Primitive a |
Instances
class (Storable a, Elt a) => PrimElt a where Source #
Element types that are primitive; arrays of these types are just a newtype wrapper over an array.
Minimal complete definition
Nothing
Methods
fromPrimitive :: forall (sh :: [Maybe Nat]). Mixed sh (Primitive a) -> Mixed sh a Source #
default fromPrimitive :: forall (sh :: [Maybe Nat]). Coercible (Mixed sh a) (Mixed sh (Primitive a)) => Mixed sh (Primitive a) -> Mixed sh a Source #
toPrimitive :: forall (sh :: [Maybe Nat]). Mixed sh a -> Mixed sh (Primitive a) Source #
data family Mixed (sh :: [Maybe Nat]) a Source #
Mixed arrays: some dimensions are size-typed, some are not. Distributes over product-typed elements using a data family so that the full array is always in struct-of-arrays format.
Built on top of XArray
which is built on top of orthotope
, meaning that
dimension permutations (e.g. mtranspose
) are typically free.
Many of the methods for working on Mixed
arrays come from the Elt
type
class.
Instances
(FloatElt a, PrimElt a) => Floating (Mixed sh a) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods exp :: Mixed sh a -> Mixed sh a # log :: Mixed sh a -> Mixed sh a # sqrt :: Mixed sh a -> Mixed sh a # (**) :: Mixed sh a -> Mixed sh a -> Mixed sh a # logBase :: Mixed sh a -> Mixed sh a -> Mixed sh a # sin :: Mixed sh a -> Mixed sh a # cos :: Mixed sh a -> Mixed sh a # tan :: Mixed sh a -> Mixed sh a # asin :: Mixed sh a -> Mixed sh a # acos :: Mixed sh a -> Mixed sh a # atan :: Mixed sh a -> Mixed sh a # sinh :: Mixed sh a -> Mixed sh a # cosh :: Mixed sh a -> Mixed sh a # tanh :: Mixed sh a -> Mixed sh a # asinh :: Mixed sh a -> Mixed sh a # acosh :: Mixed sh a -> Mixed sh a # atanh :: Mixed sh a -> Mixed sh a # log1p :: Mixed sh a -> Mixed sh a # expm1 :: Mixed sh a -> Mixed sh a # | |||||
Generic (Mixed sh CInt) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh Int32) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh Int64) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh (Primitive a)) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh (Ranked n a)) Source # | |||||
Defined in Data.Array.Nested.Ranked.Base Associated Types
| |||||
Generic (Mixed sh (Shaped sh' a)) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base Associated Types
| |||||
Generic (Mixed sh (a, b)) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh ()) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh Bool) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh Double) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh Float) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh Int) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
Generic (Mixed sh1 (Mixed sh2 a)) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
(NumElt a, PrimElt a) => Num (Mixed sh a) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
(FloatElt a, PrimElt a) => Fractional (Mixed sh a) Source # | |||||
(Show a, Elt a) => Show (Mixed sh a) Source # | |||||
Elt a => NFData (Mixed sh a) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
Eq (Mixed sh CInt) Source # | |||||
Eq (Mixed sh Int32) Source # | |||||
Eq (Mixed sh Int64) Source # | |||||
(Eq a, Storable a) => Eq (Mixed sh (Primitive a)) Source # | |||||
Eq (Mixed sh (Mixed (Replicate n ('Nothing :: Maybe Nat)) a)) => Eq (Mixed sh (Ranked n a)) Source # | |||||
Eq (Mixed sh (Mixed (MapJust sh') a)) => Eq (Mixed sh (Shaped sh' a)) Source # | |||||
(Eq (Mixed sh a), Eq (Mixed sh b)) => Eq (Mixed sh (a, b)) Source # | |||||
Eq (Mixed sh ()) Source # | |||||
Eq (Mixed sh Bool) Source # | |||||
Eq (Mixed sh Double) Source # | |||||
Eq (Mixed sh Float) Source # | |||||
Eq (Mixed sh Int) Source # | |||||
Eq (Mixed (sh1 ++ sh2) a) => Eq (Mixed sh1 (Mixed sh2 a)) Source # | |||||
Ord (Mixed sh CInt) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh CInt -> Mixed sh CInt -> Ordering # (<) :: Mixed sh CInt -> Mixed sh CInt -> Bool # (<=) :: Mixed sh CInt -> Mixed sh CInt -> Bool # (>) :: Mixed sh CInt -> Mixed sh CInt -> Bool # (>=) :: Mixed sh CInt -> Mixed sh CInt -> Bool # | |||||
Ord (Mixed sh Int32) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh Int32 -> Mixed sh Int32 -> Ordering # (<) :: Mixed sh Int32 -> Mixed sh Int32 -> Bool # (<=) :: Mixed sh Int32 -> Mixed sh Int32 -> Bool # (>) :: Mixed sh Int32 -> Mixed sh Int32 -> Bool # (>=) :: Mixed sh Int32 -> Mixed sh Int32 -> Bool # | |||||
Ord (Mixed sh Int64) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh Int64 -> Mixed sh Int64 -> Ordering # (<) :: Mixed sh Int64 -> Mixed sh Int64 -> Bool # (<=) :: Mixed sh Int64 -> Mixed sh Int64 -> Bool # (>) :: Mixed sh Int64 -> Mixed sh Int64 -> Bool # (>=) :: Mixed sh Int64 -> Mixed sh Int64 -> Bool # | |||||
(Ord a, Storable a) => Ord (Mixed sh (Primitive a)) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Ordering # (<) :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Bool # (<=) :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Bool # (>) :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Bool # (>=) :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Bool # max :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Mixed sh (Primitive a) # min :: Mixed sh (Primitive a) -> Mixed sh (Primitive a) -> Mixed sh (Primitive a) # | |||||
(Ord (Mixed sh a), Ord (Mixed sh b)) => Ord (Mixed sh (a, b)) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh (a, b) -> Mixed sh (a, b) -> Ordering # (<) :: Mixed sh (a, b) -> Mixed sh (a, b) -> Bool # (<=) :: Mixed sh (a, b) -> Mixed sh (a, b) -> Bool # (>) :: Mixed sh (a, b) -> Mixed sh (a, b) -> Bool # (>=) :: Mixed sh (a, b) -> Mixed sh (a, b) -> Bool # max :: Mixed sh (a, b) -> Mixed sh (a, b) -> Mixed sh (a, b) # min :: Mixed sh (a, b) -> Mixed sh (a, b) -> Mixed sh (a, b) # | |||||
Ord (Mixed sh ()) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
Ord (Mixed sh Bool) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh Bool -> Mixed sh Bool -> Ordering # (<) :: Mixed sh Bool -> Mixed sh Bool -> Bool # (<=) :: Mixed sh Bool -> Mixed sh Bool -> Bool # (>) :: Mixed sh Bool -> Mixed sh Bool -> Bool # (>=) :: Mixed sh Bool -> Mixed sh Bool -> Bool # | |||||
Ord (Mixed sh Double) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh Double -> Mixed sh Double -> Ordering # (<) :: Mixed sh Double -> Mixed sh Double -> Bool # (<=) :: Mixed sh Double -> Mixed sh Double -> Bool # (>) :: Mixed sh Double -> Mixed sh Double -> Bool # (>=) :: Mixed sh Double -> Mixed sh Double -> Bool # max :: Mixed sh Double -> Mixed sh Double -> Mixed sh Double # min :: Mixed sh Double -> Mixed sh Double -> Mixed sh Double # | |||||
Ord (Mixed sh Float) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh Float -> Mixed sh Float -> Ordering # (<) :: Mixed sh Float -> Mixed sh Float -> Bool # (<=) :: Mixed sh Float -> Mixed sh Float -> Bool # (>) :: Mixed sh Float -> Mixed sh Float -> Bool # (>=) :: Mixed sh Float -> Mixed sh Float -> Bool # | |||||
Ord (Mixed sh Int) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
Ord (Mixed (sh1 ++ sh2) a) => Ord (Mixed sh1 (Mixed sh2 a)) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods compare :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Ordering # (<) :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Bool # (<=) :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Bool # (>) :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Bool # (>=) :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Bool # max :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) # min :: Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) -> Mixed sh1 (Mixed sh2 a) # | |||||
Elt a => Elt (Mixed sh' a) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> IIxX sh -> Mixed sh' a Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh'0 :: [Maybe Nat]). Mixed (sh ++ sh'0) (Mixed sh' a) -> IIxX sh -> Mixed sh'0 (Mixed sh' a) Source # mscalar :: Mixed sh' a -> Mixed ('[] :: [Maybe Nat]) (Mixed sh' a) Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh (Mixed sh' a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Mixed sh' a) Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) (Mixed sh' a) -> [Mixed sh (Mixed sh' a)] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh'0 :: [Maybe Nat]) b. Storable b => StaticShX sh'0 -> XArray (sh1 ++ sh'0) b -> XArray (sh2 ++ sh'0) b) -> Mixed sh1 (Mixed sh' a) -> Mixed sh2 (Mixed sh' a) Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh'0 :: [Maybe Nat]) b. Storable b => StaticShX sh'0 -> XArray (sh1 ++ sh'0) b -> XArray (sh2 ++ sh'0) b -> XArray (sh3 ++ sh'0) b) -> Mixed sh1 (Mixed sh' a) -> Mixed sh2 (Mixed sh' a) -> Mixed sh3 (Mixed sh' a) Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh'0 :: [Maybe Nat]) b. Storable b => StaticShX sh'0 -> NonEmpty (XArray (sh1 ++ sh'0) b) -> NonEmpty (XArray (sh2 ++ sh'0) b)) -> NonEmpty (Mixed sh1 (Mixed sh' a)) -> NonEmpty (Mixed sh2 (Mixed sh' a)) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh'0 :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh'0 -> Mixed (sh1 ++ sh'0) (Mixed sh' a) -> Mixed (sh2 ++ sh'0) (Mixed sh' a) Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh (Mixed sh' a) -> Mixed (PermutePrefix is sh) (Mixed sh' a) Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) (Mixed sh' a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Mixed sh' a) Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> () Source # mshapeTree :: Mixed sh' a -> ShapeTree (Mixed sh' a) Source # mshapeTreeEq :: Proxy (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> Bool Source # mshapeTreeEmpty :: Proxy (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> Bool Source # mshowShapeTree :: Proxy (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Mixed sh' a -> MixedVecs s sh (Mixed sh' a) -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh'0 :: [Maybe Nat]) s. IShX (sh ++ sh'0) -> IIxX sh -> Mixed sh'0 (Mixed sh' a) -> MixedVecs s (sh ++ sh'0) (Mixed sh' a) -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh (Mixed sh' a) -> ST s (Mixed sh (Mixed sh' a)) Source # | |||||
(KnownShX sh', KnownElt a) => KnownElt (Mixed sh' a) Source # | |||||
Defined in Data.Array.Nested.Mixed Methods memptyArrayUnsafe :: forall (sh :: [Maybe Nat]). IShX sh -> Mixed sh (Mixed sh' a) Source # mvecsUnsafeNew :: forall (sh :: [Maybe Nat]) s. IShX sh -> Mixed sh' a -> ST s (MixedVecs s sh (Mixed sh' a)) Source # mvecsNewEmpty :: forall s (sh :: [Maybe Nat]). Proxy (Mixed sh' a) -> ST s (MixedVecs s sh (Mixed sh' a)) Source # | |||||
newtype Mixed sh CInt Source # | |||||
newtype Mixed sh Int32 Source # | |||||
newtype Mixed sh Int64 Source # | |||||
newtype Mixed sh () Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
newtype Mixed sh Bool Source # | |||||
newtype Mixed sh Double Source # | |||||
newtype Mixed sh Float Source # | |||||
newtype Mixed sh Int Source # | |||||
data MixedVecs s sh1 (Mixed sh2 a) Source # | |||||
data Mixed sh (Primitive a) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
newtype Mixed sh (Ranked n a) Source # | |||||
newtype Mixed sh (Shaped sh' a) Source # | |||||
data Mixed sh (a, b) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
data Mixed sh1 (Mixed sh2 a) Source # | |||||
type Rep (Mixed sh CInt) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
type Rep (Mixed sh Int32) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh Int32) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "M_Int32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mixed sh (Primitive Int32))))) | |||||
type Rep (Mixed sh Int64) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh Int64) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "M_Int64" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mixed sh (Primitive Int64))))) | |||||
type Rep (Mixed sh (Primitive a)) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh (Primitive a)) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'False) (C1 ('MetaCons "M_Primitive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IShX sh)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (XArray sh a)))) | |||||
type Rep (Mixed sh (Ranked n a)) Source # | |||||
Defined in Data.Array.Nested.Ranked.Base type Rep (Mixed sh (Ranked n a)) = D1 ('MetaData "Mixed" "Data.Array.Nested.Ranked.Base" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "M_Ranked" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mixed sh (Mixed (Replicate n ('Nothing :: Maybe Nat)) a))))) | |||||
type Rep (Mixed sh (Shaped sh' a)) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base type Rep (Mixed sh (Shaped sh' a)) = D1 ('MetaData "Mixed" "Data.Array.Nested.Shaped.Base" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "M_Shaped" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mixed sh (Mixed (MapJust sh') a))))) | |||||
type Rep (Mixed sh (a, b)) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh (a, b)) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'False) (C1 ('MetaCons "M_Tup2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Mixed sh a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Mixed sh b)))) | |||||
type Rep (Mixed sh ()) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
type Rep (Mixed sh Bool) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
type Rep (Mixed sh Double) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh Double) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "M_Double" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mixed sh (Primitive Double))))) | |||||
type Rep (Mixed sh Float) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh Float) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "M_Float" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mixed sh (Primitive Float))))) | |||||
type Rep (Mixed sh Int) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
type Rep (Mixed sh1 (Mixed sh2 a)) Source # | |||||
Defined in Data.Array.Nested.Mixed type Rep (Mixed sh1 (Mixed sh2 a)) = D1 ('MetaData "Mixed" "Data.Array.Nested.Mixed" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'False) (C1 ('MetaCons "M_Nest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (IShX sh1)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Mixed (sh1 ++ sh2) a)))) | |||||
type ShapeTree (Mixed sh' a) Source # | |||||
Defined in Data.Array.Nested.Mixed |
data family MixedVecs s (sh :: [Maybe Nat]) a Source #
Instances
newtype MixedVecs s sh CInt Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh Int32 Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh Int64 Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh () Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh Bool Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh Double Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh Float Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh Int Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh (Primitive a) Source # | |
Defined in Data.Array.Nested.Mixed | |
newtype MixedVecs s sh (Ranked n a) Source # | |
newtype MixedVecs s sh (Shaped sh' a) Source # | |
data MixedVecs s sh (a, b) Source # | |
Defined in Data.Array.Nested.Mixed | |
data MixedVecs s sh1 (Mixed sh2 a) Source # | |
mliftNumElt1 :: forall a b (sh :: [Maybe Nat]). (PrimElt a, PrimElt b) => (SNat (Rank sh) -> Array (Rank sh) a -> Array (Rank sh) b) -> Mixed sh a -> Mixed sh b Source #
mliftNumElt2 :: forall a b c (sh :: [Maybe Nat]). (PrimElt a, PrimElt b, PrimElt c) => (SNat (Rank sh) -> Array (Rank sh) a -> Array (Rank sh) b -> Array (Rank sh) c) -> Mixed sh a -> Mixed sh b -> Mixed sh c Source #
mquotArray :: forall a (sh :: [Maybe Nat]). (IntElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a Source #
mremArray :: forall a (sh :: [Maybe Nat]). (IntElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a Source #
matan2Array :: forall a (sh :: [Maybe Nat]). (FloatElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a Source #
Allowable element types in a mixed array, and by extension in a Ranked
or
Shaped
array. Note the polymorphic instance for Elt
of
; see the documentation for Primitive
aPrimitive
for more details.
Methods
mshape :: forall (sh :: [Maybe Nat]). Mixed sh a -> IShX sh Source #
mindex :: forall (sh :: [Maybe Nat]). Mixed sh a -> IIxX sh -> a Source #
mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') a -> IIxX sh -> Mixed sh' a Source #
mscalar :: a -> Mixed ('[] :: [Maybe Nat]) a Source #
mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh a) -> Mixed (('Nothing :: Maybe Nat) ': sh) a Source #
All arrays in the list, even subarrays inside a
, must have the same
shape; if they do not, a runtime error will be thrown. See the
documentation of mgenerate
for more information about this restriction.
Furthermore, the length of the list must correspond with n
: if n
is
Just m
and m
does not equal the length of the list, a runtime error is
thrown.
Consider also mfromListPrim
, which can avoid intermediate arrays.
mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) a -> [Mixed sh a] Source #
mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 a -> Mixed sh2 a Source #
Note: this library makes no particular guarantees about the shapes of
arrays "inside" an empty array. With mlift
, mlift2
and mliftL
you can see the
full XArray
and as such you can distinguish different empty arrays by
the "shapes" of their elements. This information is meaningless, so you
should not use it.
mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 a -> Mixed sh2 a -> Mixed sh3 a Source #
See the documentation for mlift
.
mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 a) -> NonEmpty (Mixed sh2 a) Source #
All arrays in the input must have equal shapes, including subarrays inside their elements.
mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') a -> Mixed (sh2 ++ sh') a Source #
mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh a -> Mixed (PermutePrefix is sh) a Source #
mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) a) -> Mixed (('Nothing :: Maybe Nat) ': sh) a Source #
All arrays in the input must have equal shapes, including subarrays inside their elements.
mrnf :: forall (sh :: [Maybe Nat]). Mixed sh a -> () Source #
mshapeTree :: a -> ShapeTree a Source #
mshapeTreeEq :: Proxy a -> ShapeTree a -> ShapeTree a -> Bool Source #
mshapeTreeEmpty :: Proxy a -> ShapeTree a -> Bool Source #
mshowShapeTree :: Proxy a -> ShapeTree a -> String Source #
marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh a -> Bag [Int] Source #
Returns the stride vector of each underlying component array making up this mixed array.
mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> a -> MixedVecs s sh a -> ST s () Source #
Given the shape of this array, an index and a value, write the value at that index in the vectors.
mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' a -> MixedVecs s (sh ++ sh') a -> ST s () Source #
Given the shape of this array, an index and a value, write the value at that index in the vectors.
mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh a -> ST s (Mixed sh a) Source #
Given the shape of this array, finalise the vectors into XArray
s.
Instances
Elt CInt Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh CInt -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh CInt -> IIxX sh -> CInt Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') CInt -> IIxX sh -> Mixed sh' CInt Source # mscalar :: CInt -> Mixed ('[] :: [Maybe Nat]) CInt Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh CInt) -> Mixed (('Nothing :: Maybe Nat) ': sh) CInt Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) CInt -> [Mixed sh CInt] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 CInt -> Mixed sh2 CInt Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 CInt -> Mixed sh2 CInt -> Mixed sh3 CInt Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 CInt) -> NonEmpty (Mixed sh2 CInt) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') CInt -> Mixed (sh2 ++ sh') CInt Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh CInt -> Mixed (PermutePrefix is sh) CInt Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) CInt) -> Mixed (('Nothing :: Maybe Nat) ': sh) CInt Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh CInt -> () Source # mshapeTree :: CInt -> ShapeTree CInt Source # mshapeTreeEq :: Proxy CInt -> ShapeTree CInt -> ShapeTree CInt -> Bool Source # mshapeTreeEmpty :: Proxy CInt -> ShapeTree CInt -> Bool Source # mshowShapeTree :: Proxy CInt -> ShapeTree CInt -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh CInt -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> CInt -> MixedVecs s sh CInt -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' CInt -> MixedVecs s (sh ++ sh') CInt -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh CInt -> ST s (Mixed sh CInt) Source # | |||||
Elt Int32 Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh Int32 -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh Int32 -> IIxX sh -> Int32 Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') Int32 -> IIxX sh -> Mixed sh' Int32 Source # mscalar :: Int32 -> Mixed ('[] :: [Maybe Nat]) Int32 Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh Int32) -> Mixed (('Nothing :: Maybe Nat) ': sh) Int32 Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) Int32 -> [Mixed sh Int32] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 Int32 -> Mixed sh2 Int32 Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 Int32 -> Mixed sh2 Int32 -> Mixed sh3 Int32 Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 Int32) -> NonEmpty (Mixed sh2 Int32) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') Int32 -> Mixed (sh2 ++ sh') Int32 Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh Int32 -> Mixed (PermutePrefix is sh) Int32 Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) Int32) -> Mixed (('Nothing :: Maybe Nat) ': sh) Int32 Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh Int32 -> () Source # mshapeTree :: Int32 -> ShapeTree Int32 Source # mshapeTreeEq :: Proxy Int32 -> ShapeTree Int32 -> ShapeTree Int32 -> Bool Source # mshapeTreeEmpty :: Proxy Int32 -> ShapeTree Int32 -> Bool Source # mshowShapeTree :: Proxy Int32 -> ShapeTree Int32 -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh Int32 -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Int32 -> MixedVecs s sh Int32 -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' Int32 -> MixedVecs s (sh ++ sh') Int32 -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh Int32 -> ST s (Mixed sh Int32) Source # | |||||
Elt Int64 Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh Int64 -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh Int64 -> IIxX sh -> Int64 Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') Int64 -> IIxX sh -> Mixed sh' Int64 Source # mscalar :: Int64 -> Mixed ('[] :: [Maybe Nat]) Int64 Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh Int64) -> Mixed (('Nothing :: Maybe Nat) ': sh) Int64 Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) Int64 -> [Mixed sh Int64] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 Int64 -> Mixed sh2 Int64 Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 Int64 -> Mixed sh2 Int64 -> Mixed sh3 Int64 Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 Int64) -> NonEmpty (Mixed sh2 Int64) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') Int64 -> Mixed (sh2 ++ sh') Int64 Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh Int64 -> Mixed (PermutePrefix is sh) Int64 Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) Int64) -> Mixed (('Nothing :: Maybe Nat) ': sh) Int64 Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh Int64 -> () Source # mshapeTree :: Int64 -> ShapeTree Int64 Source # mshapeTreeEq :: Proxy Int64 -> ShapeTree Int64 -> ShapeTree Int64 -> Bool Source # mshapeTreeEmpty :: Proxy Int64 -> ShapeTree Int64 -> Bool Source # mshowShapeTree :: Proxy Int64 -> ShapeTree Int64 -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh Int64 -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Int64 -> MixedVecs s sh Int64 -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' Int64 -> MixedVecs s (sh ++ sh') Int64 -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh Int64 -> ST s (Mixed sh Int64) Source # | |||||
Elt () Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh () -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh () -> IIxX sh -> () Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') () -> IIxX sh -> Mixed sh' () Source # mscalar :: () -> Mixed ('[] :: [Maybe Nat]) () Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh ()) -> Mixed (('Nothing :: Maybe Nat) ': sh) () Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) () -> [Mixed sh ()] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 () -> Mixed sh2 () Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 () -> Mixed sh2 () -> Mixed sh3 () Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 ()) -> NonEmpty (Mixed sh2 ()) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') () -> Mixed (sh2 ++ sh') () Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh () -> Mixed (PermutePrefix is sh) () Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) ()) -> Mixed (('Nothing :: Maybe Nat) ': sh) () Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh () -> () Source # mshapeTree :: () -> ShapeTree () Source # mshapeTreeEq :: Proxy () -> ShapeTree () -> ShapeTree () -> Bool Source # mshapeTreeEmpty :: Proxy () -> ShapeTree () -> Bool Source # mshowShapeTree :: Proxy () -> ShapeTree () -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh () -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> () -> MixedVecs s sh () -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' () -> MixedVecs s (sh ++ sh') () -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh () -> ST s (Mixed sh ()) Source # | |||||
Elt Bool Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh Bool -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh Bool -> IIxX sh -> Bool Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') Bool -> IIxX sh -> Mixed sh' Bool Source # mscalar :: Bool -> Mixed ('[] :: [Maybe Nat]) Bool Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh Bool) -> Mixed (('Nothing :: Maybe Nat) ': sh) Bool Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) Bool -> [Mixed sh Bool] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 Bool -> Mixed sh2 Bool Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 Bool -> Mixed sh2 Bool -> Mixed sh3 Bool Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 Bool) -> NonEmpty (Mixed sh2 Bool) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') Bool -> Mixed (sh2 ++ sh') Bool Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh Bool -> Mixed (PermutePrefix is sh) Bool Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) Bool) -> Mixed (('Nothing :: Maybe Nat) ': sh) Bool Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh Bool -> () Source # mshapeTree :: Bool -> ShapeTree Bool Source # mshapeTreeEq :: Proxy Bool -> ShapeTree Bool -> ShapeTree Bool -> Bool Source # mshapeTreeEmpty :: Proxy Bool -> ShapeTree Bool -> Bool Source # mshowShapeTree :: Proxy Bool -> ShapeTree Bool -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh Bool -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Bool -> MixedVecs s sh Bool -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' Bool -> MixedVecs s (sh ++ sh') Bool -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh Bool -> ST s (Mixed sh Bool) Source # | |||||
Elt Double Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh Double -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh Double -> IIxX sh -> Double Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') Double -> IIxX sh -> Mixed sh' Double Source # mscalar :: Double -> Mixed ('[] :: [Maybe Nat]) Double Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh Double) -> Mixed (('Nothing :: Maybe Nat) ': sh) Double Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) Double -> [Mixed sh Double] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 Double -> Mixed sh2 Double Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 Double -> Mixed sh2 Double -> Mixed sh3 Double Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 Double) -> NonEmpty (Mixed sh2 Double) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') Double -> Mixed (sh2 ++ sh') Double Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh Double -> Mixed (PermutePrefix is sh) Double Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) Double) -> Mixed (('Nothing :: Maybe Nat) ': sh) Double Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh Double -> () Source # mshapeTree :: Double -> ShapeTree Double Source # mshapeTreeEq :: Proxy Double -> ShapeTree Double -> ShapeTree Double -> Bool Source # mshapeTreeEmpty :: Proxy Double -> ShapeTree Double -> Bool Source # mshowShapeTree :: Proxy Double -> ShapeTree Double -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh Double -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Double -> MixedVecs s sh Double -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' Double -> MixedVecs s (sh ++ sh') Double -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh Double -> ST s (Mixed sh Double) Source # | |||||
Elt Float Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh Float -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh Float -> IIxX sh -> Float Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') Float -> IIxX sh -> Mixed sh' Float Source # mscalar :: Float -> Mixed ('[] :: [Maybe Nat]) Float Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh Float) -> Mixed (('Nothing :: Maybe Nat) ': sh) Float Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) Float -> [Mixed sh Float] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 Float -> Mixed sh2 Float Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 Float -> Mixed sh2 Float -> Mixed sh3 Float Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 Float) -> NonEmpty (Mixed sh2 Float) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') Float -> Mixed (sh2 ++ sh') Float Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh Float -> Mixed (PermutePrefix is sh) Float Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) Float) -> Mixed (('Nothing :: Maybe Nat) ': sh) Float Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh Float -> () Source # mshapeTree :: Float -> ShapeTree Float Source # mshapeTreeEq :: Proxy Float -> ShapeTree Float -> ShapeTree Float -> Bool Source # mshapeTreeEmpty :: Proxy Float -> ShapeTree Float -> Bool Source # mshowShapeTree :: Proxy Float -> ShapeTree Float -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh Float -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Float -> MixedVecs s sh Float -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' Float -> MixedVecs s (sh ++ sh') Float -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh Float -> ST s (Mixed sh Float) Source # | |||||
Elt Int Source # | |||||
Defined in Data.Array.Nested.Mixed Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh Int -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh Int -> IIxX sh -> Int Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') Int -> IIxX sh -> Mixed sh' Int Source # mscalar :: Int -> Mixed ('[] :: [Maybe Nat]) Int Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh Int) -> Mixed (('Nothing :: Maybe Nat) ': sh) Int Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) Int -> [Mixed sh Int] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 Int -> Mixed sh2 Int Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 Int -> Mixed sh2 Int -> Mixed sh3 Int Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 Int) -> NonEmpty (Mixed sh2 Int) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') Int -> Mixed (sh2 ++ sh') Int Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh Int -> Mixed (PermutePrefix is sh) Int Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) Int) -> Mixed (('Nothing :: Maybe Nat) ': sh) Int Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh Int -> () Source # mshapeTree :: Int -> ShapeTree Int Source # mshapeTreeEq :: Proxy Int -> ShapeTree Int -> ShapeTree Int -> Bool Source # mshapeTreeEmpty :: Proxy Int -> ShapeTree Int -> Bool Source # mshowShapeTree :: Proxy Int -> ShapeTree Int -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh Int -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Int -> MixedVecs s sh Int -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' Int -> MixedVecs s (sh ++ sh') Int -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh Int -> ST s (Mixed sh Int) Source # | |||||
Storable a => Elt (Primitive a) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh (Primitive a) -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh (Primitive a) -> IIxX sh -> Primitive a Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') (Primitive a) -> IIxX sh -> Mixed sh' (Primitive a) Source # mscalar :: Primitive a -> Mixed ('[] :: [Maybe Nat]) (Primitive a) Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh (Primitive a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Primitive a) Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) (Primitive a) -> [Mixed sh (Primitive a)] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 (Primitive a) -> Mixed sh2 (Primitive a) Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 (Primitive a) -> Mixed sh2 (Primitive a) -> Mixed sh3 (Primitive a) Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 (Primitive a)) -> NonEmpty (Mixed sh2 (Primitive a)) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') (Primitive a) -> Mixed (sh2 ++ sh') (Primitive a) Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh (Primitive a) -> Mixed (PermutePrefix is sh) (Primitive a) Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) (Primitive a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Primitive a) Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh (Primitive a) -> () Source # mshapeTree :: Primitive a -> ShapeTree (Primitive a) Source # mshapeTreeEq :: Proxy (Primitive a) -> ShapeTree (Primitive a) -> ShapeTree (Primitive a) -> Bool Source # mshapeTreeEmpty :: Proxy (Primitive a) -> ShapeTree (Primitive a) -> Bool Source # mshowShapeTree :: Proxy (Primitive a) -> ShapeTree (Primitive a) -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh (Primitive a) -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Primitive a -> MixedVecs s sh (Primitive a) -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' (Primitive a) -> MixedVecs s (sh ++ sh') (Primitive a) -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh (Primitive a) -> ST s (Mixed sh (Primitive a)) Source # | |||||
Elt a => Elt (Mixed sh' a) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> IIxX sh -> Mixed sh' a Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh'0 :: [Maybe Nat]). Mixed (sh ++ sh'0) (Mixed sh' a) -> IIxX sh -> Mixed sh'0 (Mixed sh' a) Source # mscalar :: Mixed sh' a -> Mixed ('[] :: [Maybe Nat]) (Mixed sh' a) Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh (Mixed sh' a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Mixed sh' a) Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) (Mixed sh' a) -> [Mixed sh (Mixed sh' a)] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh'0 :: [Maybe Nat]) b. Storable b => StaticShX sh'0 -> XArray (sh1 ++ sh'0) b -> XArray (sh2 ++ sh'0) b) -> Mixed sh1 (Mixed sh' a) -> Mixed sh2 (Mixed sh' a) Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh'0 :: [Maybe Nat]) b. Storable b => StaticShX sh'0 -> XArray (sh1 ++ sh'0) b -> XArray (sh2 ++ sh'0) b -> XArray (sh3 ++ sh'0) b) -> Mixed sh1 (Mixed sh' a) -> Mixed sh2 (Mixed sh' a) -> Mixed sh3 (Mixed sh' a) Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh'0 :: [Maybe Nat]) b. Storable b => StaticShX sh'0 -> NonEmpty (XArray (sh1 ++ sh'0) b) -> NonEmpty (XArray (sh2 ++ sh'0) b)) -> NonEmpty (Mixed sh1 (Mixed sh' a)) -> NonEmpty (Mixed sh2 (Mixed sh' a)) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh'0 :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh'0 -> Mixed (sh1 ++ sh'0) (Mixed sh' a) -> Mixed (sh2 ++ sh'0) (Mixed sh' a) Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh (Mixed sh' a) -> Mixed (PermutePrefix is sh) (Mixed sh' a) Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) (Mixed sh' a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Mixed sh' a) Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> () Source # mshapeTree :: Mixed sh' a -> ShapeTree (Mixed sh' a) Source # mshapeTreeEq :: Proxy (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> Bool Source # mshapeTreeEmpty :: Proxy (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> Bool Source # mshowShapeTree :: Proxy (Mixed sh' a) -> ShapeTree (Mixed sh' a) -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh (Mixed sh' a) -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Mixed sh' a -> MixedVecs s sh (Mixed sh' a) -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh'0 :: [Maybe Nat]) s. IShX (sh ++ sh'0) -> IIxX sh -> Mixed sh'0 (Mixed sh' a) -> MixedVecs s (sh ++ sh'0) (Mixed sh' a) -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh (Mixed sh' a) -> ST s (Mixed sh (Mixed sh' a)) Source # | |||||
Elt a => Elt (Ranked n a) Source # | |||||
Defined in Data.Array.Nested.Ranked.Base Associated Types
Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh (Ranked n a) -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh (Ranked n a) -> IIxX sh -> Ranked n a Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') (Ranked n a) -> IIxX sh -> Mixed sh' (Ranked n a) Source # mscalar :: Ranked n a -> Mixed ('[] :: [Maybe Nat]) (Ranked n a) Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh (Ranked n a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Ranked n a) Source # mtoListOuter :: forall (n0 :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n0 ': sh) (Ranked n a) -> [Mixed sh (Ranked n a)] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 (Ranked n a) -> Mixed sh2 (Ranked n a) Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 (Ranked n a) -> Mixed sh2 (Ranked n a) -> Mixed sh3 (Ranked n a) Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 (Ranked n a)) -> NonEmpty (Mixed sh2 (Ranked n a)) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') (Ranked n a) -> Mixed (sh2 ++ sh') (Ranked n a) Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh (Ranked n a) -> Mixed (PermutePrefix is sh) (Ranked n a) Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) (Ranked n a)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (Ranked n a) Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh (Ranked n a) -> () Source # mshapeTree :: Ranked n a -> ShapeTree (Ranked n a) Source # mshapeTreeEq :: Proxy (Ranked n a) -> ShapeTree (Ranked n a) -> ShapeTree (Ranked n a) -> Bool Source # mshapeTreeEmpty :: Proxy (Ranked n a) -> ShapeTree (Ranked n a) -> Bool Source # mshowShapeTree :: Proxy (Ranked n a) -> ShapeTree (Ranked n a) -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh (Ranked n a) -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> Ranked n a -> MixedVecs s sh (Ranked n a) -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' (Ranked n a) -> MixedVecs s (sh ++ sh') (Ranked n a) -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh (Ranked n a) -> ST s (Mixed sh (Ranked n a)) Source # | |||||
Elt a => Elt (Shaped sh a) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base Associated Types
Methods mshape :: forall (sh0 :: [Maybe Nat]). Mixed sh0 (Shaped sh a) -> IShX sh0 Source # mindex :: forall (sh0 :: [Maybe Nat]). Mixed sh0 (Shaped sh a) -> IIxX sh0 -> Shaped sh a Source # mindexPartial :: forall (sh0 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh0 ++ sh') (Shaped sh a) -> IIxX sh0 -> Mixed sh' (Shaped sh a) Source # mscalar :: Shaped sh a -> Mixed ('[] :: [Maybe Nat]) (Shaped sh a) Source # mfromListOuter :: forall (sh0 :: [Maybe Nat]). NonEmpty (Mixed sh0 (Shaped sh a)) -> Mixed (('Nothing :: Maybe Nat) ': sh0) (Shaped sh a) Source # mtoListOuter :: forall (n :: Maybe Nat) (sh0 :: [Maybe Nat]). Mixed (n ': sh0) (Shaped sh a) -> [Mixed sh0 (Shaped sh a)] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b) -> Mixed sh1 (Shaped sh a) -> Mixed sh2 (Shaped sh a) Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (sh1 ++ sh') b -> XArray (sh2 ++ sh') b -> XArray (sh3 ++ sh') b) -> Mixed sh1 (Shaped sh a) -> Mixed sh2 (Shaped sh a) -> Mixed sh3 (Shaped sh a) Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b) -> NonEmpty (XArray (sh2 ++ sh') b)) -> NonEmpty (Mixed sh1 (Shaped sh a)) -> NonEmpty (Mixed sh2 (Shaped sh a)) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') (Shaped sh a) -> Mixed (sh2 ++ sh') (Shaped sh a) Source # mtranspose :: forall (is :: [Natural]) (sh0 :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh0) => Perm is -> Mixed sh0 (Shaped sh a) -> Mixed (PermutePrefix is sh0) (Shaped sh a) Source # mconcat :: forall (sh0 :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh0) (Shaped sh a)) -> Mixed (('Nothing :: Maybe Nat) ': sh0) (Shaped sh a) Source # mrnf :: forall (sh0 :: [Maybe Nat]). Mixed sh0 (Shaped sh a) -> () Source # mshapeTree :: Shaped sh a -> ShapeTree (Shaped sh a) Source # mshapeTreeEq :: Proxy (Shaped sh a) -> ShapeTree (Shaped sh a) -> ShapeTree (Shaped sh a) -> Bool Source # mshapeTreeEmpty :: Proxy (Shaped sh a) -> ShapeTree (Shaped sh a) -> Bool Source # mshowShapeTree :: Proxy (Shaped sh a) -> ShapeTree (Shaped sh a) -> String Source # marrayStrides :: forall (sh0 :: [Maybe Nat]). Mixed sh0 (Shaped sh a) -> Bag [Int] Source # mvecsWrite :: forall (sh0 :: [Maybe Nat]) s. IShX sh0 -> IIxX sh0 -> Shaped sh a -> MixedVecs s sh0 (Shaped sh a) -> ST s () Source # mvecsWritePartial :: forall (sh0 :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh0 ++ sh') -> IIxX sh0 -> Mixed sh' (Shaped sh a) -> MixedVecs s (sh0 ++ sh') (Shaped sh a) -> ST s () Source # mvecsFreeze :: forall (sh0 :: [Maybe Nat]) s. IShX sh0 -> MixedVecs s sh0 (Shaped sh a) -> ST s (Mixed sh0 (Shaped sh a)) Source # | |||||
(Elt a, Elt b) => Elt (a, b) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
Methods mshape :: forall (sh :: [Maybe Nat]). Mixed sh (a, b) -> IShX sh Source # mindex :: forall (sh :: [Maybe Nat]). Mixed sh (a, b) -> IIxX sh -> (a, b) Source # mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Mixed (sh ++ sh') (a, b) -> IIxX sh -> Mixed sh' (a, b) Source # mscalar :: (a, b) -> Mixed ('[] :: [Maybe Nat]) (a, b) Source # mfromListOuter :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed sh (a, b)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (a, b) Source # mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Mixed (n ': sh) (a, b) -> [Mixed sh (a, b)] Source # mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b0. Storable b0 => StaticShX sh' -> XArray (sh1 ++ sh') b0 -> XArray (sh2 ++ sh') b0) -> Mixed sh1 (a, b) -> Mixed sh2 (a, b) Source # mlift2 :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh3 :: [Maybe Nat]). StaticShX sh3 -> (forall (sh' :: [Maybe Nat]) b0. Storable b0 => StaticShX sh' -> XArray (sh1 ++ sh') b0 -> XArray (sh2 ++ sh') b0 -> XArray (sh3 ++ sh') b0) -> Mixed sh1 (a, b) -> Mixed sh2 (a, b) -> Mixed sh3 (a, b) Source # mliftL :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). StaticShX sh2 -> (forall (sh' :: [Maybe Nat]) b0. Storable b0 => StaticShX sh' -> NonEmpty (XArray (sh1 ++ sh') b0) -> NonEmpty (XArray (sh2 ++ sh') b0)) -> NonEmpty (Mixed sh1 (a, b)) -> NonEmpty (Mixed sh2 (a, b)) Source # mcastPartial :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh' :: [Maybe Nat]). Rank sh1 ~ Rank sh2 => StaticShX sh1 -> StaticShX sh2 -> Proxy sh' -> Mixed (sh1 ++ sh') (a, b) -> Mixed (sh2 ++ sh') (a, b) Source # mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh (a, b) -> Mixed (PermutePrefix is sh) (a, b) Source # mconcat :: forall (sh :: [Maybe Nat]). NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) (a, b)) -> Mixed (('Nothing :: Maybe Nat) ': sh) (a, b) Source # mrnf :: forall (sh :: [Maybe Nat]). Mixed sh (a, b) -> () Source # mshapeTree :: (a, b) -> ShapeTree (a, b) Source # mshapeTreeEq :: Proxy (a, b) -> ShapeTree (a, b) -> ShapeTree (a, b) -> Bool Source # mshapeTreeEmpty :: Proxy (a, b) -> ShapeTree (a, b) -> Bool Source # mshowShapeTree :: Proxy (a, b) -> ShapeTree (a, b) -> String Source # marrayStrides :: forall (sh :: [Maybe Nat]). Mixed sh (a, b) -> Bag [Int] Source # mvecsWrite :: forall (sh :: [Maybe Nat]) s. IShX sh -> IIxX sh -> (a, b) -> MixedVecs s sh (a, b) -> ST s () Source # mvecsWritePartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) s. IShX (sh ++ sh') -> IIxX sh -> Mixed sh' (a, b) -> MixedVecs s (sh ++ sh') (a, b) -> ST s () Source # mvecsFreeze :: forall (sh :: [Maybe Nat]) s. IShX sh -> MixedVecs s sh (a, b) -> ST s (Mixed sh (a, b)) Source # |
class Elt a => KnownElt a where Source #
Element types for which we have evidence of the (static part of the) shape
in a type class constraint. Compare the instance contexts of the instances
of this class with those of Elt
: some instances have an additional
"known-shape" constraint.
This class is (currently) only required for memptyArray
and mgenerate
.
Methods
memptyArrayUnsafe :: forall (sh :: [Maybe Nat]). IShX sh -> Mixed sh a Source #
Create an empty array. The given shape must have size zero; this may or may not be checked.
mvecsUnsafeNew :: forall (sh :: [Maybe Nat]) s. IShX sh -> a -> ST s (MixedVecs s sh a) Source #
Create uninitialised vectors for this array type, given the shape of this vector and an example for the contents.
mvecsNewEmpty :: forall s (sh :: [Maybe Nat]). Proxy a -> ST s (MixedVecs s sh a) Source #
Instances
KnownElt CInt Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt Int32 Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt Int64 Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt () Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt Bool Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt Double Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt Float Source # | |
Defined in Data.Array.Nested.Mixed | |
KnownElt Int Source # | |
Defined in Data.Array.Nested.Mixed | |
Storable a => KnownElt (Primitive a) Source # | |
Defined in Data.Array.Nested.Mixed Methods memptyArrayUnsafe :: forall (sh :: [Maybe Nat]). IShX sh -> Mixed sh (Primitive a) Source # mvecsUnsafeNew :: forall (sh :: [Maybe Nat]) s. IShX sh -> Primitive a -> ST s (MixedVecs s sh (Primitive a)) Source # mvecsNewEmpty :: forall s (sh :: [Maybe Nat]). Proxy (Primitive a) -> ST s (MixedVecs s sh (Primitive a)) Source # | |
(KnownShX sh', KnownElt a) => KnownElt (Mixed sh' a) Source # | |
Defined in Data.Array.Nested.Mixed Methods memptyArrayUnsafe :: forall (sh :: [Maybe Nat]). IShX sh -> Mixed sh (Mixed sh' a) Source # mvecsUnsafeNew :: forall (sh :: [Maybe Nat]) s. IShX sh -> Mixed sh' a -> ST s (MixedVecs s sh (Mixed sh' a)) Source # mvecsNewEmpty :: forall s (sh :: [Maybe Nat]). Proxy (Mixed sh' a) -> ST s (MixedVecs s sh (Mixed sh' a)) Source # | |
(KnownNat n, KnownElt a) => KnownElt (Ranked n a) Source # | |
Defined in Data.Array.Nested.Ranked.Base Methods memptyArrayUnsafe :: forall (sh :: [Maybe Nat]). IShX sh -> Mixed sh (Ranked n a) Source # mvecsUnsafeNew :: forall (sh :: [Maybe Nat]) s. IShX sh -> Ranked n a -> ST s (MixedVecs s sh (Ranked n a)) Source # mvecsNewEmpty :: forall s (sh :: [Maybe Nat]). Proxy (Ranked n a) -> ST s (MixedVecs s sh (Ranked n a)) Source # | |
(KnownShS sh, KnownElt a) => KnownElt (Shaped sh a) Source # | |
Defined in Data.Array.Nested.Shaped.Base Methods memptyArrayUnsafe :: forall (sh0 :: [Maybe Nat]). IShX sh0 -> Mixed sh0 (Shaped sh a) Source # mvecsUnsafeNew :: forall (sh0 :: [Maybe Nat]) s. IShX sh0 -> Shaped sh a -> ST s (MixedVecs s sh0 (Shaped sh a)) Source # mvecsNewEmpty :: forall s (sh0 :: [Maybe Nat]). Proxy (Shaped sh a) -> ST s (MixedVecs s sh0 (Shaped sh a)) Source # | |
(KnownElt a, KnownElt b) => KnownElt (a, b) Source # | |
Defined in Data.Array.Nested.Mixed |
memptyArray :: forall a (sh :: [Maybe Nat]). KnownElt a => IShX sh -> Mixed ('Just 0 ': sh) a Source #
msize :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> Int Source #
The total number of elements in the array.
mgenerate :: forall (sh :: [Maybe Nat]) a. KnownElt a => IShX sh -> (IIxX sh -> a) -> Mixed sh a Source #
Create an array given a size and a function that computes the element at a given index.
WARNING: It is required that every a
returned by the argument to
mgenerate
has the same shape. For example, the following will throw a
runtime error:
foo :: Mixed [Nothing] (Mixed [Nothing] Double) foo = mgenerate (10 :.: ZIR) $ \(i :.: ZIR) -> mgenerate (i :.: ZIR) $ \(j :.: ZIR) -> ...
because the size of the inner mgenerate
is not always the same (it depends
on i
). Nested arrays in ox-arrays
are always stored fully flattened, so
the entire hierarchy (after distributing out tuples) must be a rectangular
array. The type of mgenerate
allows this requirement to be broken very
easily, hence the runtime check.
msumOuter1P :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (Storable a, NumElt a) => Mixed (n ': sh) (Primitive a) -> Mixed sh (Primitive a) Source #
msumOuter1 :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (NumElt a, PrimElt a) => Mixed (n ': sh) a -> Mixed sh a Source #
mappend :: forall (n :: Maybe Nat) (m :: Maybe Nat) (sh :: [Maybe Nat]) a. Elt a => Mixed (n ': sh) a -> Mixed (m ': sh) a -> Mixed (AddMaybe n m ': sh) a Source #
mfromVectorP :: forall (sh :: [Maybe Nat]) a. Storable a => IShX sh -> Vector a -> Mixed sh (Primitive a) Source #
mfromVector :: forall (sh :: [Maybe Nat]) a. PrimElt a => IShX sh -> Vector a -> Mixed sh a Source #
mtoVectorP :: forall a (sh :: [Maybe Nat]). Storable a => Mixed sh (Primitive a) -> Vector a Source #
mfromListLinear :: forall (sh :: [Maybe Nat]) a. Elt a => IShX sh -> NonEmpty a -> Mixed sh a Source #
mfromListPrimLinear :: forall a (sh :: [Maybe Nat]). PrimElt a => IShX sh -> [a] -> Mixed sh a Source #
mnest :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Elt a => StaticShX sh -> Mixed (sh ++ sh') a -> Mixed sh (Mixed sh' a) Source #
munNest :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Mixed sh (Mixed sh' a) -> Mixed (sh ++ sh') a Source #
mzip :: forall a b (sh :: [Maybe Nat]). (Elt a, Elt b) => Mixed sh a -> Mixed sh b -> Mixed sh (a, b) Source #
The arguments must have equal shapes. If they do not, an error is raised.
mrerankP :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh :: [Maybe Nat]) a b. (Storable a, Storable b) => StaticShX sh -> IShX sh2 -> (Mixed sh1 (Primitive a) -> Mixed sh2 (Primitive b)) -> Mixed (sh ++ sh1) (Primitive a) -> Mixed (sh ++ sh2) (Primitive b) Source #
mrerank :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (sh :: [Maybe Nat]) a b. (PrimElt a, PrimElt b) => StaticShX sh -> IShX sh2 -> (Mixed sh1 a -> Mixed sh2 b) -> Mixed (sh ++ sh1) a -> Mixed (sh ++ sh2) b Source #
See the caveats at X.rerank
.
mreplicate :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Elt a => IShX sh -> Mixed sh' a -> Mixed (sh ++ sh') a Source #
mreplicateScalP :: forall (sh :: [Maybe Nat]) a. Storable a => IShX sh -> a -> Mixed sh (Primitive a) Source #
mslice :: forall a (i :: Nat) (n :: Nat) (k :: Natural) (sh :: [Maybe Natural]). Elt a => SNat i -> SNat n -> Mixed ('Just ((i + n) + k) ': sh) a -> Mixed ('Just n ': sh) a Source #
msliceU :: forall a (sh :: [Maybe Nat]). Elt a => Int -> Int -> Mixed (('Nothing :: Maybe Nat) ': sh) a -> Mixed (('Nothing :: Maybe Nat) ': sh) a Source #
mrev1 :: forall a (n :: Maybe Nat) (sh :: [Maybe Nat]). Elt a => Mixed (n ': sh) a -> Mixed (n ': sh) a Source #
mreshape :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a. Elt a => IShX sh' -> Mixed sh a -> Mixed sh' a Source #
mminIndexPrim :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> IIxX sh Source #
Throws if the array is empty.
mmaxIndexPrim :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> IIxX sh Source #
Throws if the array is empty.
mdot1Inner :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (PrimElt a, NumElt a) => Proxy n -> Mixed (sh ++ '[n]) a -> Mixed (sh ++ '[n]) a -> Mixed sh a Source #
mdot :: forall a (sh :: [Maybe Nat]). (PrimElt a, NumElt a) => Mixed sh a -> Mixed sh a -> a Source #
This has a temporary, suboptimal implementation in terms of mflatten
.
Prefer mdot1Inner
if applicable.
mtoXArrayPrimP :: forall (sh :: [Maybe Nat]) a. Mixed sh (Primitive a) -> (IShX sh, XArray sh a) Source #
mtoXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => Mixed sh a -> (IShX sh, XArray sh a) Source #
mfromXArrayPrimP :: forall (sh :: [Maybe Nat]) a. StaticShX sh -> XArray sh a -> Mixed sh (Primitive a) Source #
mfromXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => StaticShX sh -> XArray sh a -> Mixed sh a Source #