Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Array.Nested.Shaped
Synopsis
- newtype Shaped (sh :: [Nat]) a = Shaped (Mixed (MapJust sh) a)
- squotArray :: forall a (sh :: [Nat]). (IntElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a
- sremArray :: forall a (sh :: [Nat]). (IntElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a
- satan2Array :: forall a (sh :: [Nat]). (FloatElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a
- sshape :: forall (sh :: [Nat]) a. Elt a => Shaped sh a -> ShS sh
- srank :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> SNat (Rank sh)
- ssize :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> Int
- sindex :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> IIxS sh -> a
- sindexPartial :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) a. Elt a => Shaped (sh1 ++ sh2) a -> IIxS sh1 -> Shaped sh2 a
- sgenerate :: forall (sh :: [Nat]) a. KnownElt a => ShS sh -> (IIxS sh -> a) -> Shaped sh a
- ssumOuter1 :: forall (sh :: [Nat]) (n :: Nat) a. (NumElt a, PrimElt a) => Shaped (n ': sh) a -> Shaped sh a
- ssumAllPrim :: forall a (n :: [Nat]). (PrimElt a, NumElt a) => Shaped n a -> a
- stranspose :: forall (is :: [Natural]) (sh :: [Nat]) a. (IsPermutation is, Rank is <= Rank sh, Elt a) => Perm is -> Shaped sh a -> Shaped (PermutePrefix is sh) a
- sappend :: forall a (n :: Nat) (sh :: [Nat]) (m :: Nat). Elt a => Shaped (n ': sh) a -> Shaped (m ': sh) a -> Shaped ((n + m) ': sh) a
- sscalar :: Elt a => a -> Shaped ('[] :: [Nat]) a
- sfromVector :: forall a (sh :: [Nat]). PrimElt a => ShS sh -> Vector a -> Shaped sh a
- stoVector :: forall a (sh :: [Nat]). PrimElt a => Shaped sh a -> Vector a
- sunScalar :: Elt a => Shaped ('[] :: [Nat]) a -> a
- semptyArray :: forall a (sh :: [Nat]). KnownElt a => ShS sh -> Shaped (0 ': sh) a
- srerank :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (sh :: [Nat]) a b. (PrimElt a, PrimElt b) => ShS sh -> ShS sh2 -> (Shaped sh1 a -> Shaped sh2 b) -> Shaped (sh ++ sh1) a -> Shaped (sh ++ sh2) b
- sreplicate :: forall (sh :: [Nat]) (sh' :: [Nat]) a. Elt a => ShS sh -> Shaped sh' a -> Shaped (sh ++ sh') a
- sreplicateScal :: forall a (sh :: [Nat]). PrimElt a => ShS sh -> a -> Shaped sh a
- sfromList1 :: forall a (n :: Nat). Elt a => SNat n -> NonEmpty a -> Shaped '[n] a
- sfromListOuter :: forall a (n :: Nat) (sh :: [Nat]). Elt a => SNat n -> NonEmpty (Shaped sh a) -> Shaped (n ': sh) a
- sfromListLinear :: forall (sh :: [Nat]) a. Elt a => ShS sh -> NonEmpty a -> Shaped sh a
- sfromListPrim :: forall (n :: Nat) a. PrimElt a => SNat n -> [a] -> Shaped '[n] a
- sfromListPrimLinear :: forall a (sh :: [Nat]). PrimElt a => ShS sh -> [a] -> Shaped sh a
- stoList :: forall a (n :: Nat). Elt a => Shaped '[n] a -> [a]
- stoListOuter :: forall a (n :: Nat) (sh :: [Nat]). Elt a => Shaped (n ': sh) a -> [Shaped sh a]
- stoListLinear :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> [a]
- sslice :: forall a (i :: Nat) (n :: Nat) (k :: Natural) (sh :: [Natural]). Elt a => SNat i -> SNat n -> Shaped (((i + n) + k) ': sh) a -> Shaped (n ': sh) a
- srev1 :: forall a (n :: Nat) (sh :: [Nat]). Elt a => Shaped (n ': sh) a -> Shaped (n ': sh) a
- sreshape :: forall a (sh :: [Natural]) (sh' :: [Natural]). (Elt a, Product sh ~ Product sh') => ShS sh' -> Shaped sh a -> Shaped sh' a
- sflatten :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> Shaped '[Product sh] a
- siota :: forall a (n :: Nat). (Enum a, PrimElt a) => SNat n -> Shaped '[n] a
- sminIndexPrim :: forall a (sh :: [Nat]). (PrimElt a, NumElt a) => Shaped sh a -> IIxS sh
- smaxIndexPrim :: forall a (sh :: [Nat]). (PrimElt a, NumElt a) => Shaped sh a -> IIxS sh
- sdot1Inner :: forall (sh :: [Nat]) (n :: Nat) a. (PrimElt a, NumElt a) => Proxy n -> Shaped (sh ++ '[n]) a -> Shaped (sh ++ '[n]) a -> Shaped sh a
- sdot :: forall a (sh :: [Nat]). (PrimElt a, NumElt a) => Shaped sh a -> Shaped sh a -> a
- snest :: forall (sh :: [Nat]) (sh' :: [Nat]) a. Elt a => ShS sh -> Shaped (sh ++ sh') a -> Shaped sh (Shaped sh' a)
- sunNest :: forall (sh :: [Nat]) (sh' :: [Nat]) a. Elt a => Shaped sh (Shaped sh' a) -> Shaped (sh ++ sh') a
- szip :: forall a b (sh :: [Nat]). (Elt a, Elt b) => Shaped sh a -> Shaped sh b -> Shaped sh (a, b)
- sunzip :: forall (sh :: [Nat]) a b. Shaped sh (a, b) -> (Shaped sh a, Shaped sh b)
- slift :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) a. Elt a => ShS sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (MapJust sh1 ++ sh') b -> XArray (MapJust sh2 ++ sh') b) -> Shaped sh1 a -> Shaped sh2 a
- slift2 :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (sh3 :: [Nat]) a. Elt a => ShS sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (MapJust sh1 ++ sh') b -> XArray (MapJust sh2 ++ sh') b -> XArray (MapJust sh3 ++ sh') b) -> Shaped sh1 a -> Shaped sh2 a -> Shaped sh3 a
- stoXArrayPrim :: forall a (sh :: [Nat]). PrimElt a => Shaped sh a -> (ShS sh, XArray (MapJust sh) a)
- sfromXArrayPrim :: forall a (sh :: [Nat]). PrimElt a => ShS sh -> XArray (MapJust sh) a -> Shaped sh a
- sfromOrthotope :: forall a (sh :: [Nat]). PrimElt a => ShS sh -> Array sh a -> Shaped sh a
- stoOrthotope :: forall a (sh :: [Nat]). PrimElt a => Shaped sh a -> Array sh a
- shsTakeIx :: forall (sh' :: [Nat]) (sh :: [Nat]). Proxy sh' -> ShS (sh ++ sh') -> IIxS sh -> ShS sh
- ssumOuter1P :: forall (sh :: [Nat]) (n :: Nat) a. (Storable a, NumElt a) => Shaped (n ': sh) (Primitive a) -> Shaped sh (Primitive a)
- sfromPrimitive :: forall a (sh :: [Nat]). PrimElt a => Shaped sh (Primitive a) -> Shaped sh a
- stoPrimitive :: forall a (sh :: [Nat]). PrimElt a => Shaped sh a -> Shaped sh (Primitive a)
- sfromVectorP :: forall a (sh :: [Nat]). Storable a => ShS sh -> Vector a -> Shaped sh (Primitive a)
- stoVectorP :: forall a (sh :: [Nat]). Storable a => Shaped sh (Primitive a) -> Vector a
- srerankP :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (sh :: [Nat]) a b. (Storable a, Storable b) => ShS sh -> ShS sh2 -> (Shaped sh1 (Primitive a) -> Shaped sh2 (Primitive b)) -> Shaped (sh ++ sh1) (Primitive a) -> Shaped (sh ++ sh2) (Primitive b)
- sreplicateScalP :: forall (sh :: [Nat]) a. Storable a => ShS sh -> a -> Shaped sh (Primitive a)
- stoXArrayPrimP :: forall (sh :: [Nat]) a. Shaped sh (Primitive a) -> (ShS sh, XArray (MapJust sh) a)
- sfromXArrayPrimP :: forall (sh :: [Nat]) a. ShS sh -> XArray (MapJust sh) a -> Shaped sh (Primitive a)
- liftShaped1 :: forall (sh :: [Nat]) a b. (Mixed (MapJust sh) a -> Mixed (MapJust sh) b) -> Shaped sh a -> Shaped sh b
- liftShaped2 :: forall (sh :: [Nat]) a b c. (Mixed (MapJust sh) a -> Mixed (MapJust sh) b -> Mixed (MapJust sh) c) -> Shaped sh a -> Shaped sh b -> Shaped sh c
Documentation
newtype Shaped (sh :: [Nat]) a Source #
A shape-typed array: the full shape of the array (the sizes of its
dimensions) is represented on the type level as a list of Nat
s. Note that
these are GHC.TypeLits naturals, because we do not need induction over
them and we want very large arrays to be possible.
Like for Ranked
, the valid elements are described by the Elt
type class,
and Shaped
itself is again an instance of Elt
as well.
Instances
(FloatElt a, PrimElt a) => Floating (Shaped sh a) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base Methods exp :: Shaped sh a -> Shaped sh a # log :: Shaped sh a -> Shaped sh a # sqrt :: Shaped sh a -> Shaped sh a # (**) :: Shaped sh a -> Shaped sh a -> Shaped sh a # logBase :: Shaped sh a -> Shaped sh a -> Shaped sh a # sin :: Shaped sh a -> Shaped sh a # cos :: Shaped sh a -> Shaped sh a # tan :: Shaped sh a -> Shaped sh a # asin :: Shaped sh a -> Shaped sh a # acos :: Shaped sh a -> Shaped sh a # atan :: Shaped sh a -> Shaped sh a # sinh :: Shaped sh a -> Shaped sh a # cosh :: Shaped sh a -> Shaped sh a # tanh :: Shaped sh a -> Shaped sh a # asinh :: Shaped sh a -> Shaped sh a # acosh :: Shaped sh a -> Shaped sh a # atanh :: Shaped sh a -> Shaped sh a # log1p :: Shaped sh a -> Shaped sh a # expm1 :: Shaped sh a -> Shaped sh a # | |||||
Generic (Mixed sh (Shaped sh' a)) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base Associated Types
| |||||
(NumElt a, PrimElt a) => Num (Shaped sh a) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base Methods (+) :: Shaped sh a -> Shaped sh a -> Shaped sh a # (-) :: Shaped sh a -> Shaped sh a -> Shaped sh a # (*) :: Shaped sh a -> Shaped sh a -> Shaped sh a # negate :: Shaped sh a -> Shaped sh a # abs :: Shaped sh a -> Shaped sh a # signum :: Shaped sh a -> Shaped sh a # fromInteger :: Integer -> Shaped sh a # | |||||
(FloatElt a, PrimElt a) => Fractional (Shaped sh a) Source # | |||||
(Show a, Elt a) => Show (Shaped n a) Source # | |||||
Elt a => NFData (Shaped sh a) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base | |||||
Eq (Mixed sh (Mixed (MapJust sh') a)) => Eq (Mixed sh (Shaped sh' a)) Source # | |||||
Eq (Mixed (MapJust sh) a) => Eq (Shaped sh a) Source # | |||||
Ord (Mixed (MapJust sh) a) => Ord (Shaped sh a) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base | |||||
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 # | |||||
(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 # | |||||
newtype MixedVecs s sh (Shaped sh' a) Source # | |||||
newtype Mixed sh (Shaped sh' a) Source # | |||||
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 ShapeTree (Shaped sh a) Source # | |||||
Defined in Data.Array.Nested.Shaped.Base |
squotArray :: forall a (sh :: [Nat]). (IntElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a Source #
sremArray :: forall a (sh :: [Nat]). (IntElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a Source #
satan2Array :: forall a (sh :: [Nat]). (FloatElt a, PrimElt a) => Shaped sh a -> Shaped sh a -> Shaped sh a Source #
ssize :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> Int Source #
The total number of elements in the array.
sindexPartial :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) a. Elt a => Shaped (sh1 ++ sh2) a -> IIxS sh1 -> Shaped sh2 a Source #
sgenerate :: forall (sh :: [Nat]) a. KnownElt a => ShS sh -> (IIxS sh -> a) -> Shaped sh a Source #
WARNING: All values returned from the function must have equal shape.
See the documentation of mgenerate
for more details.
ssumOuter1 :: forall (sh :: [Nat]) (n :: Nat) a. (NumElt a, PrimElt a) => Shaped (n ': sh) a -> Shaped sh a Source #
stranspose :: forall (is :: [Natural]) (sh :: [Nat]) a. (IsPermutation is, Rank is <= Rank sh, Elt a) => Perm is -> Shaped sh a -> Shaped (PermutePrefix is sh) a Source #
sappend :: forall a (n :: Nat) (sh :: [Nat]) (m :: Nat). Elt a => Shaped (n ': sh) a -> Shaped (m ': sh) a -> Shaped ((n + m) ': sh) a Source #
srerank :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (sh :: [Nat]) a b. (PrimElt a, PrimElt b) => ShS sh -> ShS sh2 -> (Shaped sh1 a -> Shaped sh2 b) -> Shaped (sh ++ sh1) a -> Shaped (sh ++ sh2) b Source #
sreplicate :: forall (sh :: [Nat]) (sh' :: [Nat]) a. Elt a => ShS sh -> Shaped sh' a -> Shaped (sh ++ sh') a Source #
sfromListOuter :: forall a (n :: Nat) (sh :: [Nat]). Elt a => SNat n -> NonEmpty (Shaped sh a) -> Shaped (n ': sh) a Source #
stoListOuter :: forall a (n :: Nat) (sh :: [Nat]). Elt a => Shaped (n ': sh) a -> [Shaped sh a] Source #
sslice :: forall a (i :: Nat) (n :: Nat) (k :: Natural) (sh :: [Natural]). Elt a => SNat i -> SNat n -> Shaped (((i + n) + k) ': sh) a -> Shaped (n ': sh) a Source #
srev1 :: forall a (n :: Nat) (sh :: [Nat]). Elt a => Shaped (n ': sh) a -> Shaped (n ': sh) a Source #
sreshape :: forall a (sh :: [Natural]) (sh' :: [Natural]). (Elt a, Product sh ~ Product sh') => ShS sh' -> Shaped sh a -> Shaped sh' a Source #
sminIndexPrim :: forall a (sh :: [Nat]). (PrimElt a, NumElt a) => Shaped sh a -> IIxS sh Source #
Throws if the array is empty.
smaxIndexPrim :: forall a (sh :: [Nat]). (PrimElt a, NumElt a) => Shaped sh a -> IIxS sh Source #
Throws if the array is empty.
sdot1Inner :: forall (sh :: [Nat]) (n :: Nat) a. (PrimElt a, NumElt a) => Proxy n -> Shaped (sh ++ '[n]) a -> Shaped (sh ++ '[n]) a -> Shaped sh a Source #
sdot :: forall a (sh :: [Nat]). (PrimElt a, NumElt a) => Shaped sh a -> Shaped sh a -> a Source #
This has a temporary, suboptimal implementation in terms of mflatten
.
Prefer sdot1Inner
if applicable.
snest :: forall (sh :: [Nat]) (sh' :: [Nat]) a. Elt a => ShS sh -> Shaped (sh ++ sh') a -> Shaped sh (Shaped sh' a) Source #
sunNest :: forall (sh :: [Nat]) (sh' :: [Nat]) a. Elt a => Shaped sh (Shaped sh' a) -> Shaped (sh ++ sh') a Source #
szip :: forall a b (sh :: [Nat]). (Elt a, Elt b) => Shaped sh a -> Shaped sh b -> Shaped sh (a, b) Source #
slift :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) a. Elt a => ShS sh2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (MapJust sh1 ++ sh') b -> XArray (MapJust sh2 ++ sh') b) -> Shaped sh1 a -> Shaped sh2 a Source #
See the documentation of mlift
.
slift2 :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (sh3 :: [Nat]) a. Elt a => ShS sh3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (MapJust sh1 ++ sh') b -> XArray (MapJust sh2 ++ sh') b -> XArray (MapJust sh3 ++ sh') b) -> Shaped sh1 a -> Shaped sh2 a -> Shaped sh3 a Source #
See the documentation of mlift
.
stoXArrayPrim :: forall a (sh :: [Nat]). PrimElt a => Shaped sh a -> (ShS sh, XArray (MapJust sh) a) Source #
sfromXArrayPrim :: forall a (sh :: [Nat]). PrimElt a => ShS sh -> XArray (MapJust sh) a -> Shaped sh a Source #
shsTakeIx :: forall (sh' :: [Nat]) (sh :: [Nat]). Proxy sh' -> ShS (sh ++ sh') -> IIxS sh -> ShS sh Source #
ssumOuter1P :: forall (sh :: [Nat]) (n :: Nat) a. (Storable a, NumElt a) => Shaped (n ': sh) (Primitive a) -> Shaped sh (Primitive a) Source #
sfromPrimitive :: forall a (sh :: [Nat]). PrimElt a => Shaped sh (Primitive a) -> Shaped sh a Source #
stoPrimitive :: forall a (sh :: [Nat]). PrimElt a => Shaped sh a -> Shaped sh (Primitive a) Source #
sfromVectorP :: forall a (sh :: [Nat]). Storable a => ShS sh -> Vector a -> Shaped sh (Primitive a) Source #
srerankP :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (sh :: [Nat]) a b. (Storable a, Storable b) => ShS sh -> ShS sh2 -> (Shaped sh1 (Primitive a) -> Shaped sh2 (Primitive b)) -> Shaped (sh ++ sh1) (Primitive a) -> Shaped (sh ++ sh2) (Primitive b) Source #
sreplicateScalP :: forall (sh :: [Nat]) a. Storable a => ShS sh -> a -> Shaped sh (Primitive a) Source #
stoXArrayPrimP :: forall (sh :: [Nat]) a. Shaped sh (Primitive a) -> (ShS sh, XArray (MapJust sh) a) Source #
sfromXArrayPrimP :: forall (sh :: [Nat]) a. ShS sh -> XArray (MapJust sh) a -> Shaped sh (Primitive a) Source #