Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Array.Nested
Synopsis
- newtype Ranked (n :: Nat) a = Ranked (Mixed (Replicate n ('Nothing :: Maybe Nat)) a)
- data ListR (n :: Nat) i where
- newtype IxR (n :: Nat) i where
- type IIxR (n :: Nat) = IxR n Int
- newtype ShR (n :: Nat) i where
- type IShR (n :: Nat) = ShR n Int
- rshape :: forall a (n :: Nat). Elt a => Ranked n a -> IShR n
- rrank :: forall a (n :: Nat). Elt a => Ranked n a -> SNat n
- rsize :: forall a (n :: Nat). Elt a => Ranked n a -> Int
- rindex :: forall a (n :: Nat). Elt a => Ranked n a -> IIxR n -> a
- rindexPartial :: forall (n :: Natural) (m :: Natural) a. Elt a => Ranked (n + m) a -> IIxR n -> Ranked m a
- rgenerate :: forall (n :: Nat) a. KnownElt a => IShR n -> (IIxR n -> a) -> Ranked n a
- rsumOuter1 :: forall (n :: Natural) a. (NumElt a, PrimElt a) => Ranked (n + 1) a -> Ranked n a
- rsumAllPrim :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> a
- rtranspose :: forall (n :: Nat) a. Elt a => PermR -> Ranked n a -> Ranked n a
- rappend :: forall (n :: Natural) a. Elt a => Ranked (n + 1) a -> Ranked (n + 1) a -> Ranked (n + 1) a
- rconcat :: forall (n :: Natural) a. Elt a => NonEmpty (Ranked (n + 1) a) -> Ranked (n + 1) a
- rscalar :: Elt a => a -> Ranked 0 a
- rfromVector :: forall (n :: Nat) a. PrimElt a => IShR n -> Vector a -> Ranked n a
- rtoVector :: forall a (n :: Nat). PrimElt a => Ranked n a -> Vector a
- runScalar :: Elt a => Ranked 0 a -> a
- remptyArray :: KnownElt a => Ranked 1 a
- rrerank :: forall (n1 :: Nat) (n2 :: Nat) (n :: Nat) a b. (PrimElt a, PrimElt b) => SNat n -> IShR n2 -> (Ranked n1 a -> Ranked n2 b) -> Ranked (n + n1) a -> Ranked (n + n2) b
- rreplicate :: forall (n :: Nat) (m :: Nat) a. Elt a => IShR n -> Ranked m a -> Ranked (n + m) a
- rreplicateScal :: forall (n :: Nat) a. PrimElt a => IShR n -> a -> Ranked n a
- rfromList1 :: Elt a => NonEmpty a -> Ranked 1 a
- rfromListOuter :: forall (n :: Nat) a. Elt a => NonEmpty (Ranked n a) -> Ranked (n + 1) a
- rfromListLinear :: forall (n :: Nat) a. Elt a => IShR n -> NonEmpty a -> Ranked n a
- rfromListPrim :: PrimElt a => [a] -> Ranked 1 a
- rfromListPrimLinear :: forall a (n :: Nat). PrimElt a => IShR n -> [a] -> Ranked n a
- rtoList :: Elt a => Ranked 1 a -> [a]
- rtoListOuter :: forall (n :: Natural) a. Elt a => Ranked (n + 1) a -> [Ranked n a]
- rtoListLinear :: forall a (n :: Nat). Elt a => Ranked n a -> [a]
- rslice :: forall (n :: Natural) a. Elt a => Int -> Int -> Ranked (n + 1) a -> Ranked (n + 1) a
- rrev1 :: forall (n :: Natural) a. Elt a => Ranked (n + 1) a -> Ranked (n + 1) a
- rreshape :: forall (n :: Nat) (n' :: Nat) a. Elt a => IShR n' -> Ranked n a -> Ranked n' a
- rflatten :: forall a (n :: Nat). Elt a => Ranked n a -> Ranked 1 a
- riota :: (Enum a, PrimElt a) => Int -> Ranked 1 a
- rminIndexPrim :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> IIxR n
- rmaxIndexPrim :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> IIxR n
- rdot1Inner :: forall (n :: Natural) a. (PrimElt a, NumElt a) => Ranked (n + 1) a -> Ranked (n + 1) a -> Ranked n a
- rdot :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> Ranked n a -> a
- rnest :: forall (n :: Nat) (m :: Natural) a. Elt a => SNat n -> Ranked (n + m) a -> Ranked n (Ranked m a)
- runNest :: forall (n :: Nat) (m :: Nat) a. Elt a => Ranked n (Ranked m a) -> Ranked (n + m) a
- rzip :: forall a b (n :: Nat). (Elt a, Elt b) => Ranked n a -> Ranked n b -> Ranked n (a, b)
- runzip :: forall (n :: Nat) a b. Ranked n (a, b) -> (Ranked n a, Ranked n b)
- rlift :: forall (n1 :: Nat) (n2 :: Nat) a. Elt a => SNat n2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (Replicate n1 ('Nothing :: Maybe Nat) ++ sh') b -> XArray (Replicate n2 ('Nothing :: Maybe Nat) ++ sh') b) -> Ranked n1 a -> Ranked n2 a
- rlift2 :: forall (n1 :: Nat) (n2 :: Nat) (n3 :: Nat) a. Elt a => SNat n3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (Replicate n1 ('Nothing :: Maybe Nat) ++ sh') b -> XArray (Replicate n2 ('Nothing :: Maybe Nat) ++ sh') b -> XArray (Replicate n3 ('Nothing :: Maybe Nat) ++ sh') b) -> Ranked n1 a -> Ranked n2 a -> Ranked n3 a
- rtoXArrayPrim :: forall a (n :: Nat). PrimElt a => Ranked n a -> (IShR n, XArray (Replicate n ('Nothing :: Maybe Nat)) a)
- rfromXArrayPrim :: forall a (n :: Nat). PrimElt a => SNat n -> XArray (Replicate n ('Nothing :: Maybe Nat)) a -> Ranked n a
- rtoMixed :: forall (n :: Nat) a. Ranked n a -> Mixed (Replicate n ('Nothing :: Maybe Nat)) a
- rcastToMixed :: forall (sh :: [Maybe Nat]) (n :: Natural) a. (Rank sh ~ n, Elt a) => StaticShX sh -> Ranked n a -> Mixed sh a
- rcastToShaped :: forall a (sh :: [Nat]). Elt a => Ranked (Rank sh) a -> ShS sh -> Shaped sh a
- rfromOrthotope :: forall a (n :: Nat). PrimElt a => SNat n -> Array n a -> Ranked n a
- rtoOrthotope :: forall a (n :: Nat). PrimElt a => Ranked n a -> Array n a
- rquotArray :: forall a (n :: Nat). (IntElt a, PrimElt a) => Ranked n a -> Ranked n a -> Ranked n a
- rremArray :: forall a (n :: Nat). (IntElt a, PrimElt a) => Ranked n a -> Ranked n a -> Ranked n a
- ratan2Array :: forall a (n :: Nat). (FloatElt a, PrimElt a) => Ranked n a -> Ranked n a -> Ranked n a
- newtype Shaped (sh :: [Nat]) a = Shaped (Mixed (MapJust sh) a)
- data ListS (sh :: [Nat]) (f :: Nat -> Type) where
- newtype IxS (sh :: [Nat]) i where
- type IIxS (sh :: [Nat]) = IxS sh Int
- newtype ShS (sh :: [Nat]) where
- class KnownShS (sh :: [Nat]) where
- 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
- stoMixed :: forall (sh :: [Nat]) a. Shaped sh a -> Mixed (MapJust sh) a
- scastToMixed :: forall (sh :: [Nat]) (sh' :: [Maybe Nat]) a. (Elt a, Rank sh ~ Rank sh') => StaticShX sh' -> Shaped sh a -> Mixed sh' a
- stoRanked :: forall a (sh :: [Nat]). Elt a => Shaped sh a -> Ranked (Rank 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
- 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
- data family Mixed (sh :: [Maybe Nat]) a
- data ListX (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) where
- newtype IxX (sh :: [Maybe Nat]) i where
- type IIxX (sh :: [Maybe Nat]) = IxX sh Int
- newtype ShX (sh :: [Maybe Nat]) i where
- class KnownShX (sh :: [Maybe Nat]) where
- type IShX (sh :: [Maybe Nat]) = ShX sh Int
- newtype StaticShX (sh :: [Maybe Nat]) where
- data SMayNat i (f :: k -> Type) (n :: Maybe k) where
- mshape :: forall (sh :: [Maybe Nat]). Elt a => Mixed sh a -> IShX sh
- 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
- mindex :: forall (sh :: [Maybe Nat]). Elt a => Mixed sh a -> IIxX sh -> a
- mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Elt a => Mixed (sh ++ sh') a -> IIxX sh -> Mixed sh' a
- mgenerate :: forall (sh :: [Maybe Nat]) a. KnownElt a => IShX sh -> (IIxX sh -> a) -> Mixed sh 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
- mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (Elt a, IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh a -> Mixed (PermutePrefix is sh) 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
- mconcat :: forall (sh :: [Maybe Nat]). Elt a => NonEmpty (Mixed (('Nothing :: Maybe Nat) ': sh) a) -> Mixed (('Nothing :: Maybe Nat) ': sh) a
- mscalar :: Elt a => a -> Mixed ('[] :: [Maybe Nat]) a
- mfromVector :: forall (sh :: [Maybe Nat]) a. PrimElt a => IShX sh -> Vector a -> Mixed sh a
- mtoVector :: forall a (sh :: [Maybe Nat]). PrimElt a => Mixed sh a -> Vector a
- munScalar :: Elt a => Mixed ('[] :: [Maybe Nat]) a -> a
- memptyArray :: forall a (sh :: [Maybe Nat]). KnownElt a => IShX sh -> Mixed ('Just 0 ': sh) a
- 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
- mreplicateScal :: forall (sh :: [Maybe Nat]) a. PrimElt a => IShX sh -> a -> Mixed sh a
- mfromList1 :: Elt a => NonEmpty a -> Mixed '['Nothing :: Maybe Nat] a
- mfromListOuter :: forall (sh :: [Maybe Nat]). Elt a => NonEmpty (Mixed sh a) -> Mixed (('Nothing :: Maybe Nat) ': sh) 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]
- mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Elt a => Mixed (n ': sh) a -> [Mixed sh a]
- mtoListLinear :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> [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
- 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
- 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)
- mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). Elt a => 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]). Elt a => 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
- mtoXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => Mixed sh a -> (IShX sh, XArray sh a)
- mfromXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => StaticShX sh -> XArray sh a -> Mixed sh a
- mcast :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) a. (Rank sh1 ~ Rank sh2, Elt a) => StaticShX sh2 -> Mixed sh1 a -> Mixed sh2 a
- mcastToShaped :: forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a. (Elt a, Rank sh ~ Rank sh') => ShS sh' -> Mixed sh a -> Shaped sh' a
- mtoRanked :: forall (sh :: [Maybe Nat]) a. Elt a => Mixed sh a -> Ranked (Rank sh) a
- convert :: (Elt a, Elt b) => Conversion a b -> a -> b
- data Conversion a b where
- ConvId :: forall a. Conversion a a
- ConvCmp :: forall b1 b a. Conversion b1 b -> Conversion a b1 -> Conversion a b
- ConvRX :: forall (n :: Nat) a1. Conversion (Ranked n a1) (Mixed (Replicate n ('Nothing :: Maybe Nat)) a1)
- ConvSX :: forall (sh :: [Nat]) a1. Conversion (Shaped sh a1) (Mixed (MapJust sh) a1)
- ConvXR :: forall a1 (sh :: [Maybe Nat]). Elt a1 => Conversion (Mixed sh a1) (Ranked (Rank sh) a1)
- ConvXS :: forall (sh :: [Nat]) a1. Conversion (Mixed (MapJust sh) a1) (Shaped sh a1)
- ConvXS' :: forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a1. (Rank sh ~ Rank sh', Elt a1) => ShS sh' -> Conversion (Mixed sh a1) (Shaped sh' a1)
- ConvXX' :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a1. (Rank sh ~ Rank sh', Elt a1) => StaticShX sh' -> Conversion (Mixed sh a1) (Mixed sh' a1)
- ConvRR :: forall a1 b1 (n :: Nat). Conversion a1 b1 -> Conversion (Ranked n a1) (Ranked n b1)
- ConvSS :: forall a1 b1 (sh :: [Nat]). Conversion a1 b1 -> Conversion (Shaped sh a1) (Shaped sh b1)
- ConvXX :: forall a1 b1 (sh :: [Maybe Nat]). Conversion a1 b1 -> Conversion (Mixed sh a1) (Mixed sh b1)
- ConvT2 :: forall a1 a' b1 b'. Conversion a1 a' -> Conversion b1 b' -> Conversion (a1, b1) (a', b')
- Conv0X :: forall a. Elt a => Conversion a (Mixed ('[] :: [Maybe Nat]) a)
- ConvX0 :: forall b. Conversion (Mixed ('[] :: [Maybe Nat]) b) b
- ConvNest :: forall a1 (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Elt a1 => StaticShX sh -> Conversion (Mixed (sh ++ sh') a1) (Mixed sh (Mixed sh' a1))
- ConvUnnest :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a1. Conversion (Mixed sh (Mixed sh' a1)) (Mixed (sh ++ sh') a1)
- ConvZip :: forall a1 b1 (sh :: [Maybe Nat]). (Elt a1, Elt b1) => Conversion (Mixed sh a1, Mixed sh b1) (Mixed sh (a1, b1))
- ConvUnzip :: forall a1 b1 (sh :: [Maybe Nat]). (Elt a1, Elt b1) => Conversion (Mixed sh (a1, b1)) (Mixed sh a1, Mixed sh b1)
- 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
- class (Storable a, Elt a) => PrimElt a
- newtype Primitive a = Primitive a
- class Elt a => KnownElt a
- type family (l1 :: [a]) ++ (l2 :: [a]) :: [a] where ...
- class Storable a
- data SNat (n :: Nat)
- pattern SNat :: () => KnownNat n => SNat n
- pattern SZ :: () => n ~ 0 => SNat n
- pattern SS :: forall np1 n. () => (n + 1) ~ np1 => SNat n -> SNat np1
- data Perm (list :: [Nat]) where
- type IsPermutation (as :: [Natural]) = (AllElem as (Count 0 (Rank as)), AllElem (Count 0 (Rank as)) as)
- class KnownPerm (l :: [Nat]) where
- class NumElt a
- class NumElt a => IntElt a
- class NumElt a => FloatElt a
- type family Rank (sh :: [a]) :: Natural where ...
- type family Product (sh :: [Natural]) :: Natural where ...
- type family Replicate (n :: Natural) (a1 :: a) :: [a] where ...
- type family MapJust (l :: [a]) = (r :: [Maybe a]) | r -> a l where ...
Ranked arrays
newtype Ranked (n :: Nat) a Source #
A rank-typed array: the number of dimensions of the array (its rank) is
represented on the type level as a Nat
.
Valid elements of a ranked arrays are described by the Elt
type class.
Because Ranked
itself is also an instance of Elt
, nested arrays are
supported (and are represented as a single, flattened, struct-of-arrays
array internally).
Instances
data ListR (n :: Nat) i where Source #
Constructors
ZR :: forall i. ListR 0 i | |
(:::) :: forall (n1 :: Natural) {i}. i -> ListR n1 i -> ListR (n1 + 1) i infixr 3 |
Instances
Foldable (ListR n) Source # | |
Defined in Data.Array.Nested.Ranked.Shape Methods fold :: Monoid m => ListR n m -> m # foldMap :: Monoid m => (a -> m) -> ListR n a -> m # foldMap' :: Monoid m => (a -> m) -> ListR n a -> m # foldr :: (a -> b -> b) -> b -> ListR n a -> b # foldr' :: (a -> b -> b) -> b -> ListR n a -> b # foldl :: (b -> a -> b) -> b -> ListR n a -> b # foldl' :: (b -> a -> b) -> b -> ListR n a -> b # foldr1 :: (a -> a -> a) -> ListR n a -> a # foldl1 :: (a -> a -> a) -> ListR n a -> a # elem :: Eq a => a -> ListR n a -> Bool # maximum :: Ord a => ListR n a -> a # minimum :: Ord a => ListR n a -> a # | |
Functor (ListR n) Source # | |
KnownNat n => IsList (ListR n i) Source # | Untyped: length is checked at runtime. |
Show i => Show (ListR n i) Source # | |
NFData i => NFData (ListR n i) Source # | |
Defined in Data.Array.Nested.Ranked.Shape | |
Eq i => Eq (ListR n i) Source # | |
Ord i => Ord (ListR n i) Source # | |
type Item (ListR n i) Source # | |
Defined in Data.Array.Nested.Ranked.Shape |
newtype IxR (n :: Nat) i Source #
An index into a rank-typed array.
Bundled Patterns
pattern ZIR :: () => n ~ 0 => IxR n i | |
pattern (:.:) :: forall {n1} {i} n. () => (n + 1) ~ n1 => i -> IxR n i -> IxR n1 i infixr 3 |
Instances
Foldable (IxR n) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape Methods fold :: Monoid m => IxR n m -> m # foldMap :: Monoid m => (a -> m) -> IxR n a -> m # foldMap' :: Monoid m => (a -> m) -> IxR n a -> m # foldr :: (a -> b -> b) -> b -> IxR n a -> b # foldr' :: (a -> b -> b) -> b -> IxR n a -> b # foldl :: (b -> a -> b) -> b -> IxR n a -> b # foldl' :: (b -> a -> b) -> b -> IxR n a -> b # foldr1 :: (a -> a -> a) -> IxR n a -> a # foldl1 :: (a -> a -> a) -> IxR n a -> a # elem :: Eq a => a -> IxR n a -> Bool # maximum :: Ord a => IxR n a -> a # minimum :: Ord a => IxR n a -> a # | |||||
Functor (IxR n) Source # | |||||
Generic (IxR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape Associated Types
| |||||
KnownNat n => IsList (IxR n i) Source # | Untyped: length is checked at runtime. | ||||
Show i => Show (IxR n i) Source # | |||||
NFData i => NFData (IxR sh i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape | |||||
Eq i => Eq (IxR n i) Source # | |||||
Ord i => Ord (IxR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape | |||||
type Rep (IxR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape | |||||
type Item (IxR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape |
newtype ShR (n :: Nat) i Source #
Bundled Patterns
pattern ZSR :: () => n ~ 0 => ShR n i | |
pattern (:$:) :: forall {n1} {i} n. () => (n + 1) ~ n1 => i -> ShR n i -> ShR n1 i infixr 3 |
Instances
Foldable (ShR n) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape Methods fold :: Monoid m => ShR n m -> m # foldMap :: Monoid m => (a -> m) -> ShR n a -> m # foldMap' :: Monoid m => (a -> m) -> ShR n a -> m # foldr :: (a -> b -> b) -> b -> ShR n a -> b # foldr' :: (a -> b -> b) -> b -> ShR n a -> b # foldl :: (b -> a -> b) -> b -> ShR n a -> b # foldl' :: (b -> a -> b) -> b -> ShR n a -> b # foldr1 :: (a -> a -> a) -> ShR n a -> a # foldl1 :: (a -> a -> a) -> ShR n a -> a # elem :: Eq a => a -> ShR n a -> Bool # maximum :: Ord a => ShR n a -> a # minimum :: Ord a => ShR n a -> a # | |||||
Functor (ShR n) Source # | |||||
Generic (ShR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape Associated Types
| |||||
KnownNat n => IsList (ShR n i) Source # | Untyped: length is checked at runtime. | ||||
Show i => Show (ShR n i) Source # | |||||
NFData i => NFData (ShR sh i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape | |||||
Eq i => Eq (ShR n i) Source # | |||||
Ord i => Ord (ShR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape | |||||
type Rep (ShR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape | |||||
type Item (ShR n i) Source # | |||||
Defined in Data.Array.Nested.Ranked.Shape |
rsize :: forall a (n :: Nat). Elt a => Ranked n a -> Int Source #
The total number of elements in the array.
rindexPartial :: forall (n :: Natural) (m :: Natural) a. Elt a => Ranked (n + m) a -> IIxR n -> Ranked m a Source #
rgenerate :: forall (n :: Nat) a. KnownElt a => IShR n -> (IIxR n -> a) -> Ranked n a Source #
WARNING: All values returned from the function must have equal shape.
See the documentation of mgenerate
for more details.
rsumOuter1 :: forall (n :: Natural) a. (NumElt a, PrimElt a) => Ranked (n + 1) a -> Ranked n a Source #
rappend :: forall (n :: Natural) a. Elt a => Ranked (n + 1) a -> Ranked (n + 1) a -> Ranked (n + 1) a Source #
rconcat :: forall (n :: Natural) a. Elt a => NonEmpty (Ranked (n + 1) a) -> Ranked (n + 1) a Source #
remptyArray :: KnownElt a => Ranked 1 a Source #
rrerank :: forall (n1 :: Nat) (n2 :: Nat) (n :: Nat) a b. (PrimElt a, PrimElt b) => SNat n -> IShR n2 -> (Ranked n1 a -> Ranked n2 b) -> Ranked (n + n1) a -> Ranked (n + n2) b Source #
If there is a zero-sized dimension in the n
-prefix of the shape of the
input array, then there is no way to deduce the full shape of the output
array (more precisely, the n2
part): that could only come from calling
f
, and there are no subarrays to call f
on. orthotope
errors out in
this case; we choose to fill the n2
part of the output shape with zeros.
For example, if:
arr :: Ranked 5 Int -- of shape [3, 0, 4, 2, 21] f :: Ranked 2 Int -> Ranked 3 Float
then:
rrerank _ _ _ f arr :: Ranked 5 Float
and this result will have shape [3, 0, 4, 0, 0, 0]
. Note that the
"reranked" part (the last 3 entries) are zero; we don't know if f
intended
to return an array with shape all-0 here (it probably didn't), but there is
no better number to put here absent a subarray of the input to pass to f
.
rreplicate :: forall (n :: Nat) (m :: Nat) a. Elt a => IShR n -> Ranked m a -> Ranked (n + m) a Source #
rfromListPrim :: PrimElt a => [a] -> Ranked 1 a Source #
rslice :: forall (n :: Natural) a. Elt a => Int -> Int -> Ranked (n + 1) a -> Ranked (n + 1) a Source #
rminIndexPrim :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> IIxR n Source #
Throws if the array is empty.
rmaxIndexPrim :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> IIxR n Source #
Throws if the array is empty.
rdot1Inner :: forall (n :: Natural) a. (PrimElt a, NumElt a) => Ranked (n + 1) a -> Ranked (n + 1) a -> Ranked n a Source #
rdot :: forall a (n :: Nat). (PrimElt a, NumElt a) => Ranked n a -> Ranked n a -> a Source #
This has a temporary, suboptimal implementation in terms of mflatten
.
Prefer rdot1Inner
if applicable.
rnest :: forall (n :: Nat) (m :: Natural) a. Elt a => SNat n -> Ranked (n + m) a -> Ranked n (Ranked m a) Source #
runNest :: forall (n :: Nat) (m :: Nat) a. Elt a => Ranked n (Ranked m a) -> Ranked (n + m) a Source #
rzip :: forall a b (n :: Nat). (Elt a, Elt b) => Ranked n a -> Ranked n b -> Ranked n (a, b) Source #
Lifting orthotope operations to Ranked
arrays
rlift :: forall (n1 :: Nat) (n2 :: Nat) a. Elt a => SNat n2 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (Replicate n1 ('Nothing :: Maybe Nat) ++ sh') b -> XArray (Replicate n2 ('Nothing :: Maybe Nat) ++ sh') b) -> Ranked n1 a -> Ranked n2 a Source #
See the documentation of mlift
.
rlift2 :: forall (n1 :: Nat) (n2 :: Nat) (n3 :: Nat) a. Elt a => SNat n3 -> (forall (sh' :: [Maybe Nat]) b. Storable b => StaticShX sh' -> XArray (Replicate n1 ('Nothing :: Maybe Nat) ++ sh') b -> XArray (Replicate n2 ('Nothing :: Maybe Nat) ++ sh') b -> XArray (Replicate n3 ('Nothing :: Maybe Nat) ++ sh') b) -> Ranked n1 a -> Ranked n2 a -> Ranked n3 a Source #
See the documentation of mlift2
.
Conversions
rtoXArrayPrim :: forall a (n :: Nat). PrimElt a => Ranked n a -> (IShR n, XArray (Replicate n ('Nothing :: Maybe Nat)) a) Source #
rfromXArrayPrim :: forall a (n :: Nat). PrimElt a => SNat n -> XArray (Replicate n ('Nothing :: Maybe Nat)) a -> Ranked n a Source #
rtoMixed :: forall (n :: Nat) a. Ranked n a -> Mixed (Replicate n ('Nothing :: Maybe Nat)) a Source #
rcastToMixed :: forall (sh :: [Maybe Nat]) (n :: Natural) a. (Rank sh ~ n, Elt a) => StaticShX sh -> Ranked n a -> Mixed sh a Source #
A more weakly-typed version of rtoMixed
that does a runtime shape
compatibility check.
rcastToShaped :: forall a (sh :: [Nat]). Elt a => Ranked (Rank sh) a -> ShS sh -> Shaped sh a Source #
Additional arithmetic operations
These functions are separate top-level functions, and not exposed in
instances for RealFloat
and Integral
, because those classes include a
variety of other functions that make no sense for arrays.
This problem already occurs with fromInteger
, fromRational
and pi
, but
having Num
, Fractional
and Floating
available is just too useful.
rquotArray :: forall a (n :: Nat). (IntElt a, PrimElt a) => Ranked n a -> Ranked n a -> Ranked n a Source #
rremArray :: forall a (n :: Nat). (IntElt a, PrimElt a) => Ranked n a -> Ranked n a -> Ranked n a Source #
ratan2Array :: forall a (n :: Nat). (FloatElt a, PrimElt a) => Ranked n a -> Ranked n a -> Ranked n a Source #
Shaped arrays
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 |
data ListS (sh :: [Nat]) (f :: Nat -> Type) where Source #
Constructors
ZS :: forall (f :: Nat -> Type). ListS ('[] :: [Nat]) f | |
(::$) :: forall (n :: Nat) (sh1 :: [Nat]) {f :: Nat -> Type}. KnownNat n => f n -> ListS sh1 f -> ListS (n ': sh1) f infixr 3 |
Instances
KnownShS sh => IsList (ListS sh (Const i :: Nat -> Type)) Source # | Untyped: length is checked at runtime. |
(forall (n :: Nat). Show (f n)) => Show (ListS sh f) Source # | |
(forall (m :: Nat). NFData (f m)) => NFData (ListS n f) Source # | |
Defined in Data.Array.Nested.Shaped.Shape | |
(forall (n :: Nat). Eq (f n)) => Eq (ListS sh f) Source # | |
(forall (n :: Nat). Ord (f n)) => Ord (ListS sh f) Source # | |
Defined in Data.Array.Nested.Shaped.Shape | |
type Item (ListS sh (Const i :: Nat -> Type)) Source # | |
newtype IxS (sh :: [Nat]) i Source #
An index into a shape-typed array.
Bundled Patterns
pattern ZIS :: () => sh ~ ('[] :: [Nat]) => IxS sh i | |
pattern (:.$) :: forall {sh1} {i} (n :: Nat) sh. () => forall. (KnownNat n, (n ': sh) ~ sh1) => i -> IxS sh i -> IxS sh1 i infixr 3 | Note: The |
Instances
Foldable (IxS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape Methods fold :: Monoid m => IxS sh m -> m # foldMap :: Monoid m => (a -> m) -> IxS sh a -> m # foldMap' :: Monoid m => (a -> m) -> IxS sh a -> m # foldr :: (a -> b -> b) -> b -> IxS sh a -> b # foldr' :: (a -> b -> b) -> b -> IxS sh a -> b # foldl :: (b -> a -> b) -> b -> IxS sh a -> b # foldl' :: (b -> a -> b) -> b -> IxS sh a -> b # foldr1 :: (a -> a -> a) -> IxS sh a -> a # foldl1 :: (a -> a -> a) -> IxS sh a -> a # elem :: Eq a => a -> IxS sh a -> Bool # maximum :: Ord a => IxS sh a -> a # minimum :: Ord a => IxS sh a -> a # | |||||
Functor (IxS sh) Source # | |||||
Generic (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape Associated Types
| |||||
KnownShS sh => IsList (IxS sh i) Source # | Very untyped: only length is checked (at runtime), index bounds are not checked. | ||||
Show i => Show (IxS sh i) Source # | |||||
NFData i => NFData (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
Eq i => Eq (IxS sh i) Source # | |||||
Ord i => Ord (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
type Rep (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape type Rep (IxS sh i) = D1 ('MetaData "IxS" "Data.Array.Nested.Shaped.Shape" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "IxS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListS sh (Const i :: Nat -> Type))))) | |||||
type Item (IxS sh i) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape |
newtype ShS (sh :: [Nat]) Source #
The shape of a shape-typed array given as a list of SNat
values.
Note that because the shape of a shape-typed array is known statically, you
can also retrieve the array shape from a KnownShS
dictionary.
Bundled Patterns
pattern ZSS :: () => sh ~ ('[] :: [Nat]) => ShS sh | |
pattern (:$$) :: forall {sh1} (n :: Nat) sh. () => (KnownNat n, (n ': sh) ~ sh1) => SNat n -> ShS sh -> ShS sh1 infixr 3 |
Instances
Generic (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape Associated Types
| |||||
KnownShS sh => IsList (ShS sh) Source # | Untyped: length and values are checked at runtime. | ||||
Show (ShS sh) Source # | |||||
NFData (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
Eq (ShS sh) Source # | |||||
Ord (ShS sh) Source # | |||||
TestEquality ShS Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
type Rep (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape | |||||
type Item (ShS sh) Source # | |||||
Defined in Data.Array.Nested.Shaped.Shape |
class KnownShS (sh :: [Nat]) where Source #
Evidence for the static part of a shape. This pops up only when you are polymorphic in the element type of an array.
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 #
Lifting orthotope operations to Shaped
arrays
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
.
Conversions
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 #
scastToMixed :: forall (sh :: [Nat]) (sh' :: [Maybe Nat]) a. (Elt a, Rank sh ~ Rank sh') => StaticShX sh' -> Shaped sh a -> Mixed sh' a Source #
A more weakly-typed version of stoMixed
that does a runtime shape
compatibility check.
Additional arithmetic operations
These functions are separate top-level functions, and not exposed in
instances for RealFloat
and Integral
, because those classes include a
variety of other functions that make no sense for arrays.
This problem already occurs with fromInteger
, fromRational
and pi
, but
having Num
, Fractional
and Floating
available is just too useful.
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 #
Mixed arrays
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 ListX (sh :: [Maybe Nat]) (f :: Maybe Nat -> Type) where Source #
Constructors
ZX :: forall (f :: Maybe Nat -> Type). ListX ('[] :: [Maybe Nat]) f | |
(::%) :: forall (f :: Maybe Nat -> Type) (n :: Maybe Nat) (sh1 :: [Maybe Nat]). f n -> ListX sh1 f -> ListX (n ': sh1) f infixr 3 |
Instances
KnownShX sh => IsList (ListX sh (Const i :: Maybe Nat -> Type)) Source # | Very untyped: only length is checked (at runtime). |
Defined in Data.Array.Nested.Mixed.Shape Methods fromList :: [Item (ListX sh (Const i :: Maybe Nat -> Type))] -> ListX sh (Const i :: Maybe Nat -> Type) # fromListN :: Int -> [Item (ListX sh (Const i :: Maybe Nat -> Type))] -> ListX sh (Const i :: Maybe Nat -> Type) # toList :: ListX sh (Const i :: Maybe Nat -> Type) -> [Item (ListX sh (Const i :: Maybe Nat -> Type))] # | |
(forall (n :: Maybe Nat). Show (f n)) => Show (ListX sh f) Source # | |
(forall (n :: Maybe Nat). NFData (f n)) => NFData (ListX sh f) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
(forall (n :: Maybe Nat). Eq (f n)) => Eq (ListX sh f) Source # | |
(forall (n :: Maybe Nat). Ord (f n)) => Ord (ListX sh f) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
type Item (ListX sh (Const i :: Maybe Nat -> Type)) Source # | |
newtype IxX (sh :: [Maybe Nat]) i Source #
An index into a mixed-typed array.
Bundled Patterns
pattern ZIX :: () => sh ~ ('[] :: [Maybe Nat]) => IxX sh i | |
pattern (:.%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => forall. (n ': sh) ~ sh1 => i -> IxX sh i -> IxX sh1 i infixr 3 |
Instances
Foldable (IxX sh) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape Methods fold :: Monoid m => IxX sh m -> m # foldMap :: Monoid m => (a -> m) -> IxX sh a -> m # foldMap' :: Monoid m => (a -> m) -> IxX sh a -> m # foldr :: (a -> b -> b) -> b -> IxX sh a -> b # foldr' :: (a -> b -> b) -> b -> IxX sh a -> b # foldl :: (b -> a -> b) -> b -> IxX sh a -> b # foldl' :: (b -> a -> b) -> b -> IxX sh a -> b # foldr1 :: (a -> a -> a) -> IxX sh a -> a # foldl1 :: (a -> a -> a) -> IxX sh a -> a # elem :: Eq a => a -> IxX sh a -> Bool # maximum :: Ord a => IxX sh a -> a # minimum :: Ord a => IxX sh a -> a # | |||||
Functor (IxX sh) Source # | |||||
Generic (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape Associated Types
| |||||
KnownShX sh => IsList (IxX sh i) Source # | Very untyped: only length is checked (at runtime), index bounds are not checked. | ||||
Show i => Show (IxX sh i) Source # | |||||
NFData i => NFData (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
Eq i => Eq (IxX sh i) Source # | |||||
Ord i => Ord (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
type Rep (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape type Rep (IxX sh i) = D1 ('MetaData "IxX" "Data.Array.Nested.Mixed.Shape" "ox-arrays-0.1.0.0-G9rS3ky7ORtC6G06Mvzq1I" 'True) (C1 ('MetaCons "IxX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListX sh (Const i :: Maybe Nat -> Type))))) | |||||
type Item (IxX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape |
newtype ShX (sh :: [Maybe Nat]) i Source #
This is a newtype over ListX
.
Bundled Patterns
pattern ZSX :: () => sh ~ ('[] :: [Maybe Nat]) => ShX sh i | |
pattern (:$%) :: forall {sh1} {i} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat i SNat n -> ShX sh i -> ShX sh1 i infixr 3 |
Instances
Functor (ShX sh) Source # | |||||
Generic (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape Associated Types
| |||||
KnownShX sh => IsList (ShX sh Int) Source # | Untyped: length and known dimensions are checked (at runtime). | ||||
Defined in Data.Array.Nested.Mixed.Shape Associated Types
| |||||
Show i => Show (ShX sh i) Source # | |||||
NFData i => NFData (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
Eq i => Eq (ShX sh i) Source # | |||||
Ord i => Ord (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
type Rep (ShX sh i) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape | |||||
type Item (ShX sh Int) Source # | |||||
Defined in Data.Array.Nested.Mixed.Shape |
class KnownShX (sh :: [Maybe Nat]) where Source #
Evidence for the static part of a shape. This pops up only when you are polymorphic in the element type of an array.
newtype StaticShX (sh :: [Maybe Nat]) Source #
The part of a shape that is statically known. (A newtype over ListX
.)
Bundled Patterns
pattern ZKX :: () => sh ~ ('[] :: [Maybe Nat]) => StaticShX sh | |
pattern (:!%) :: forall {sh1} (n :: Maybe Nat) sh. () => (n ': sh) ~ sh1 => SMayNat () SNat n -> StaticShX sh -> StaticShX sh1 infixr 3 |
Instances
Show (StaticShX sh) Source # | |
NFData (StaticShX sh) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
Eq (StaticShX sh) Source # | |
Ord (StaticShX sh) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
TestEquality StaticShX Source # | |
data SMayNat i (f :: k -> Type) (n :: Maybe k) where Source #
Constructors
SUnknown :: forall {k} i (f :: k -> Type). i -> SMayNat i f ('Nothing :: Maybe k) | |
SKnown :: forall {k} (f :: k -> Type) (n1 :: k) i. f n1 -> SMayNat i f ('Just n1) |
Instances
TestEquality f => TestEquality (SMayNat i f :: Maybe k -> Type) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
(Show i, forall (m :: k). Show (f m)) => Show (SMayNat i f n) Source # | |
(NFData i, forall (m :: k). NFData (f m)) => NFData (SMayNat i f n) Source # | |
Defined in Data.Array.Nested.Mixed.Shape | |
(Eq i, forall (m :: k). Eq (f m)) => Eq (SMayNat i f n) Source # | |
(Ord i, forall (m :: k). Ord (f m)) => Ord (SMayNat i f n) Source # | |
Defined in Data.Array.Nested.Mixed.Shape Methods compare :: SMayNat i f n -> SMayNat i f n -> Ordering # (<) :: SMayNat i f n -> SMayNat i f n -> Bool # (<=) :: SMayNat i f n -> SMayNat i f n -> Bool # (>) :: SMayNat i f n -> SMayNat i f n -> Bool # (>=) :: SMayNat i f n -> SMayNat i f n -> Bool # |
msize :: forall a (sh :: [Maybe Nat]). Elt a => Mixed sh a -> Int Source #
The total number of elements in the array.
mindexPartial :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Elt a => Mixed (sh ++ sh') a -> IIxX sh -> Mixed sh' a Source #
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.
msumOuter1 :: forall (sh :: [Maybe Nat]) (n :: Maybe Nat) a. (NumElt a, PrimElt a) => Mixed (n ': sh) a -> Mixed sh a Source #
mtranspose :: forall (is :: [Natural]) (sh :: [Maybe Nat]). (Elt a, IsPermutation is, Rank is <= Rank sh) => Perm is -> Mixed sh a -> Mixed (PermutePrefix is 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 #
mconcat :: forall (sh :: [Maybe Nat]). Elt a => 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.
mfromVector :: forall (sh :: [Maybe Nat]) a. PrimElt a => IShX sh -> Vector a -> Mixed sh a Source #
memptyArray :: forall a (sh :: [Maybe Nat]). KnownElt a => IShX sh -> Mixed ('Just 0 ': sh) a 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 #
mfromListOuter :: forall (sh :: [Maybe Nat]). Elt a => 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.
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 #
mtoListOuter :: forall (n :: Maybe Nat) (sh :: [Maybe Nat]). Elt a => Mixed (n ': sh) a -> [Mixed sh 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 #
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.
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.
Lifting orthotope operations to Mixed
arrays
mlift :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]). Elt a => 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]). Elt a => 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
.
Conversions
mtoXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => Mixed sh a -> (IShX sh, XArray sh a) Source #
mfromXArrayPrim :: forall a (sh :: [Maybe Nat]). PrimElt a => StaticShX sh -> XArray sh a -> Mixed sh a Source #
mcast :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) a. (Rank sh1 ~ Rank sh2, Elt a) => StaticShX sh2 -> Mixed sh1 a -> Mixed sh2 a Source #
mcastToShaped :: forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a. (Elt a, Rank sh ~ Rank sh') => ShS sh' -> Mixed sh a -> Shaped sh' a Source #
data Conversion a b where Source #
The constructors that perform runtime shape checking are marked with a
tick ('
): ConvXS'
and ConvXX'
. For the other constructors, the types
ensure that the shapes are already compatible. To convert between Ranked
and Shaped
, go via Mixed
.
The guiding principle behind Conversion
is that it should represent the
array restructurings, or perhaps re-presentations, that do not change the
underlying XArray
s. This leads to the inclusion of some operations that do
not look like simple conversions (casts) at first glance, like ConvZip
.
Note: Haddock gleefully renames type variables in constructors so that they match the data type head as much as possible. See the source for a more readable presentation of this data type.
Constructors
ConvId :: forall a. Conversion a a | |
ConvCmp :: forall b1 b a. Conversion b1 b -> Conversion a b1 -> Conversion a b | |
ConvRX :: forall (n :: Nat) a1. Conversion (Ranked n a1) (Mixed (Replicate n ('Nothing :: Maybe Nat)) a1) | |
ConvSX :: forall (sh :: [Nat]) a1. Conversion (Shaped sh a1) (Mixed (MapJust sh) a1) | |
ConvXR :: forall a1 (sh :: [Maybe Nat]). Elt a1 => Conversion (Mixed sh a1) (Ranked (Rank sh) a1) | |
ConvXS :: forall (sh :: [Nat]) a1. Conversion (Mixed (MapJust sh) a1) (Shaped sh a1) | |
ConvXS' :: forall (sh :: [Maybe Nat]) (sh' :: [Nat]) a1. (Rank sh ~ Rank sh', Elt a1) => ShS sh' -> Conversion (Mixed sh a1) (Shaped sh' a1) | |
ConvXX' :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a1. (Rank sh ~ Rank sh', Elt a1) => StaticShX sh' -> Conversion (Mixed sh a1) (Mixed sh' a1) | |
ConvRR :: forall a1 b1 (n :: Nat). Conversion a1 b1 -> Conversion (Ranked n a1) (Ranked n b1) | |
ConvSS :: forall a1 b1 (sh :: [Nat]). Conversion a1 b1 -> Conversion (Shaped sh a1) (Shaped sh b1) | |
ConvXX :: forall a1 b1 (sh :: [Maybe Nat]). Conversion a1 b1 -> Conversion (Mixed sh a1) (Mixed sh b1) | |
ConvT2 :: forall a1 a' b1 b'. Conversion a1 a' -> Conversion b1 b' -> Conversion (a1, b1) (a', b') | |
Conv0X :: forall a. Elt a => Conversion a (Mixed ('[] :: [Maybe Nat]) a) | |
ConvX0 :: forall b. Conversion (Mixed ('[] :: [Maybe Nat]) b) b | |
ConvNest :: forall a1 (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]). Elt a1 => StaticShX sh -> Conversion (Mixed (sh ++ sh') a1) (Mixed sh (Mixed sh' a1)) | |
ConvUnnest :: forall (sh :: [Maybe Nat]) (sh' :: [Maybe Nat]) a1. Conversion (Mixed sh (Mixed sh' a1)) (Mixed (sh ++ sh') a1) | |
ConvZip :: forall a1 b1 (sh :: [Maybe Nat]). (Elt a1, Elt b1) => Conversion (Mixed sh a1, Mixed sh b1) (Mixed sh (a1, b1)) | |
ConvUnzip :: forall a1 b1 (sh :: [Maybe Nat]). (Elt a1, Elt b1) => Conversion (Mixed sh (a1, b1)) (Mixed sh a1, Mixed sh b1) |
Instances
Category Conversion Source # | |
Defined in Data.Array.Nested.Convert | |
Show (Conversion a b) Source # | |
Defined in Data.Array.Nested.Convert Methods showsPrec :: Int -> Conversion a b -> ShowS # show :: Conversion a b -> String # showList :: [Conversion a b] -> ShowS # |
Additional arithmetic operations
These functions are separate top-level functions, and not exposed in
instances for RealFloat
and Integral
, because those classes include a
variety of other functions that make no sense for arrays.
This problem already occurs with fromInteger
, fromRational
and pi
, but
having Num
, Fractional
and Floating
available is just too useful.
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 #
Array elements
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.
Minimal complete definition
mshape, mindex, mindexPartial, mscalar, mfromListOuter, mtoListOuter, mlift, mlift2, mliftL, mcastPartial, mtranspose, mconcat, mrnf, mshapeTree, mshapeTreeEq, mshapeTreeEmpty, mshowShapeTree, marrayStrides, mvecsWrite, mvecsWritePartial, mvecsFreeze
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 (Storable a, Elt a) => PrimElt a Source #
Element types that are primitive; arrays of these types are just a newtype wrapper over an array.
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
Show a => Show (Primitive a) 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 # | |||||
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 # | |||||
Generic (Mixed sh (Primitive a)) Source # | |||||
Defined in Data.Array.Nested.Mixed Associated Types
| |||||
(Eq a, Storable a) => Eq (Mixed sh (Primitive a)) Source # | |||||
(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) # | |||||
newtype MixedVecs s sh (Primitive a) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
data Mixed sh (Primitive a) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
type ShapeTree (Primitive a) Source # | |||||
Defined in Data.Array.Nested.Mixed | |||||
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)))) |
class Elt a => KnownElt a 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
.
Minimal complete definition
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 |
Further utilities / re-exports
The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.
Memory addresses are represented as values of type
, for some
Ptr
aa
which is an instance of class Storable
. The type argument to
Ptr
helps provide some valuable type safety in FFI code (you can't
mix pointers of different types without an explicit cast), while
helping the Haskell type system figure out which marshalling method is
needed for a given pointer.
All marshalling between Haskell and a foreign language ultimately
boils down to translating Haskell data structures into the binary
representation of a corresponding data structure of the foreign
language and vice versa. To code this marshalling in Haskell, it is
necessary to manipulate primitive data types stored in unstructured
memory blocks. The class Storable
facilitates this manipulation on
all types for which it is instantiated, which are the standard basic
types of Haskell, the fixed size Int
types (Int8
, Int16
,
Int32
, Int64
), the fixed size Word
types (Word8
, Word16
,
Word32
, Word64
), StablePtr
, all types from Foreign.C.Types,
as well as Ptr
.
Minimal complete definition
sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)
Instances
Storable CBool | |
Storable CChar | |
Storable CClock | |
Storable CDouble | |
Storable CFloat | |
Storable CInt | |
Defined in Foreign.C.Types | |
Storable CIntMax | |
Storable CIntPtr | |
Storable CLLong | |
Storable CLong | |
Storable CPtrdiff | |
Defined in Foreign.C.Types | |
Storable CSChar | |
Storable CSUSeconds | |
Defined in Foreign.C.Types Methods sizeOf :: CSUSeconds -> Int # alignment :: CSUSeconds -> Int # peekElemOff :: Ptr CSUSeconds -> Int -> IO CSUSeconds # pokeElemOff :: Ptr CSUSeconds -> Int -> CSUSeconds -> IO () # peekByteOff :: Ptr b -> Int -> IO CSUSeconds # pokeByteOff :: Ptr b -> Int -> CSUSeconds -> IO () # peek :: Ptr CSUSeconds -> IO CSUSeconds # poke :: Ptr CSUSeconds -> CSUSeconds -> IO () # | |
Storable CShort | |
Storable CSigAtomic | |
Defined in Foreign.C.Types Methods sizeOf :: CSigAtomic -> Int # alignment :: CSigAtomic -> Int # peekElemOff :: Ptr CSigAtomic -> Int -> IO CSigAtomic # pokeElemOff :: Ptr CSigAtomic -> Int -> CSigAtomic -> IO () # peekByteOff :: Ptr b -> Int -> IO CSigAtomic # pokeByteOff :: Ptr b -> Int -> CSigAtomic -> IO () # peek :: Ptr CSigAtomic -> IO CSigAtomic # poke :: Ptr CSigAtomic -> CSigAtomic -> IO () # | |
Storable CSize | |
Storable CTime | |
Storable CUChar | |
Storable CUInt | |
Storable CUIntMax | |
Defined in Foreign.C.Types | |
Storable CUIntPtr | |
Defined in Foreign.C.Types | |
Storable CULLong | |
Storable CULong | |
Storable CUSeconds | |
Defined in Foreign.C.Types | |
Storable CUShort | |
Storable CWchar | |
Storable IntPtr | |
Storable WordPtr | |
Storable Fingerprint | Since: base-4.4.0.0 |
Defined in Foreign.Storable Methods sizeOf :: Fingerprint -> Int # alignment :: Fingerprint -> Int # peekElemOff :: Ptr Fingerprint -> Int -> IO Fingerprint # pokeElemOff :: Ptr Fingerprint -> Int -> Fingerprint -> IO () # peekByteOff :: Ptr b -> Int -> IO Fingerprint # pokeByteOff :: Ptr b -> Int -> Fingerprint -> IO () # peek :: Ptr Fingerprint -> IO Fingerprint # poke :: Ptr Fingerprint -> Fingerprint -> IO () # | |
Storable Int16 | Since: base-2.1 |
Storable Int32 | Since: base-2.1 |
Storable Int64 | Since: base-2.1 |
Storable Int8 | Since: base-2.1 |
Defined in Foreign.Storable | |
Storable IoSubSystem | Since: base-4.9.0.0 |
Defined in GHC.RTS.Flags Methods sizeOf :: IoSubSystem -> Int # alignment :: IoSubSystem -> Int # peekElemOff :: Ptr IoSubSystem -> Int -> IO IoSubSystem # pokeElemOff :: Ptr IoSubSystem -> Int -> IoSubSystem -> IO () # peekByteOff :: Ptr b -> Int -> IO IoSubSystem # pokeByteOff :: Ptr b -> Int -> IoSubSystem -> IO () # peek :: Ptr IoSubSystem -> IO IoSubSystem # poke :: Ptr IoSubSystem -> IoSubSystem -> IO () # | |
Storable Word16 | Since: base-2.1 |
Storable Word32 | Since: base-2.1 |
Storable Word64 | Since: base-2.1 |
Storable Word8 | Since: base-2.1 |
Storable CBlkCnt | |
Storable CBlkSize | |
Defined in System.Posix.Types | |
Storable CCc | |
Defined in System.Posix.Types | |
Storable CClockId | |
Defined in System.Posix.Types | |
Storable CDev | |
Defined in System.Posix.Types | |
Storable CFsBlkCnt | |
Defined in System.Posix.Types | |
Storable CFsFilCnt | |
Defined in System.Posix.Types | |
Storable CGid | |
Defined in System.Posix.Types | |
Storable CId | |
Defined in System.Posix.Types | |
Storable CIno | |
Defined in System.Posix.Types | |
Storable CKey | |
Defined in System.Posix.Types | |
Storable CMode | |
Storable CNfds | |
Storable CNlink | |
Storable COff | |
Defined in System.Posix.Types | |
Storable CPid | |
Defined in System.Posix.Types | |
Storable CRLim | |
Storable CSocklen | |
Defined in System.Posix.Types | |
Storable CSpeed | |
Storable CSsize | |
Storable CTcflag | |
Storable CTimer | |
Storable CUid | |
Defined in System.Posix.Types | |
Storable Fd | |
Defined in System.Posix.Types | |
Storable () | Since: base-4.9.0.0 |
Defined in Foreign.Storable | |
Storable Bool | Since: base-2.1 |
Defined in Foreign.Storable | |
Storable Char | Since: base-2.1 |
Defined in Foreign.Storable | |
Storable Double | Since: base-2.1 |
Storable Float | Since: base-2.1 |
Storable Int | Since: base-2.1 |
Defined in Foreign.Storable | |
Storable Word | Since: base-2.1 |
Defined in Foreign.Storable | |
Storable a => Storable (Complex a) | Since: base-4.8.0.0 |
Defined in Data.Complex | |
Storable a => Storable (Identity a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Identity Methods alignment :: Identity a -> Int # peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) # pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () # peekByteOff :: Ptr b -> Int -> IO (Identity a) # pokeByteOff :: Ptr b -> Int -> Identity a -> IO () # | |
Storable a => Storable (Down a) | Since: base-4.14.0.0 |
Storable (ConstPtr a) | |
Defined in Foreign.Storable Methods alignment :: ConstPtr a -> Int # peekElemOff :: Ptr (ConstPtr a) -> Int -> IO (ConstPtr a) # pokeElemOff :: Ptr (ConstPtr a) -> Int -> ConstPtr a -> IO () # peekByteOff :: Ptr b -> Int -> IO (ConstPtr a) # pokeByteOff :: Ptr b -> Int -> ConstPtr a -> IO () # | |
Storable (FunPtr a) | Since: base-2.1 |
Defined in Foreign.Storable | |
Storable (Ptr a) | Since: base-2.1 |
(Storable a, Integral a) => Storable (Ratio a) | Since: base-4.8.0.0 |
Storable (StablePtr a) | Since: base-2.1 |
Defined in Foreign.Storable Methods sizeOf :: StablePtr a -> Int # alignment :: StablePtr a -> Int # peekElemOff :: Ptr (StablePtr a) -> Int -> IO (StablePtr a) # pokeElemOff :: Ptr (StablePtr a) -> Int -> StablePtr a -> IO () # peekByteOff :: Ptr b -> Int -> IO (StablePtr a) # pokeByteOff :: Ptr b -> Int -> StablePtr a -> IO () # | |
Storable g => Storable (StateGen g) | |
Defined in System.Random.Internal Methods alignment :: StateGen g -> Int # peekElemOff :: Ptr (StateGen g) -> Int -> IO (StateGen g) # pokeElemOff :: Ptr (StateGen g) -> Int -> StateGen g -> IO () # peekByteOff :: Ptr b -> Int -> IO (StateGen g) # pokeByteOff :: Ptr b -> Int -> StateGen g -> IO () # | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const |
A value-level witness for a type-level natural number. This is commonly
referred to as a singleton type, as for each n
, there is a single value
that inhabits the type
(aside from bottom).SNat
n
The definition of SNat
is intentionally left abstract. To obtain an SNat
value, use one of the following:
- The
natSing
method ofKnownNat
. - The
SNat
pattern synonym. - The
withSomeSNat
function, which creates anSNat
from aNatural
number.
Since: base-4.18.0.0
Instances
TestCoercion SNat | Since: base-4.18.0.0 |
Defined in GHC.TypeNats | |
TestEquality SNat | Since: base-4.18.0.0 |
Defined in GHC.TypeNats | |
Show (SNat n) | Since: base-4.18.0.0 |
Eq (SNat n) | Since: base-4.19.0.0 |
Ord (SNat n) | Since: base-4.19.0.0 |
pattern SNat :: () => KnownNat n => SNat n #
A explicitly bidirectional pattern synonym relating an SNat
to a
KnownNat
constraint.
As an expression: Constructs an explicit
value from an
implicit SNat
n
constraint:KnownNat
n
SNat @n ::KnownNat
n =>SNat
n
As a pattern: Matches on an explicit
value bringing
an implicit SNat
n
constraint into scope:KnownNat
n
f :: SNat
n -> ..
f SNat = {- SNat n in scope -}
Since: base-4.18.0.0
data Perm (list :: [Nat]) where Source #
A "backward" permutation of a dimension list. The operation on the
dimension list is most similar to backpermute
; see Permute
for code that implements this.
Constructors
PNil :: Perm ('[] :: [Nat]) | |
PCons :: forall (a :: Nat) (l :: [Nat]). SNat a -> Perm l -> Perm (a ': l) infixr 5 |
type IsPermutation (as :: [Natural]) = (AllElem as (Count 0 (Rank as)), AllElem (Count 0 (Rank as)) as) Source #
class KnownPerm (l :: [Nat]) where Source #
Utility class for generating permutations from type class information.
Minimal complete definition
numEltAdd, numEltSub, numEltMul, numEltNeg, numEltAbs, numEltSignum, numEltSum1Inner, numEltProduct1Inner, numEltSumFull, numEltProductFull, numEltMinIndex, numEltMaxIndex, numEltDotprodInner
Instances
NumElt CInt | |
Defined in Data.Array.Strided.Arith.Internal Methods numEltAdd :: forall (n :: Nat). SNat n -> Array n CInt -> Array n CInt -> Array n CInt # numEltSub :: forall (n :: Nat). SNat n -> Array n CInt -> Array n CInt -> Array n CInt # numEltMul :: forall (n :: Nat). SNat n -> Array n CInt -> Array n CInt -> Array n CInt # numEltNeg :: forall (n :: Nat). SNat n -> Array n CInt -> Array n CInt # numEltAbs :: forall (n :: Nat). SNat n -> Array n CInt -> Array n CInt # numEltSignum :: forall (n :: Nat). SNat n -> Array n CInt -> Array n CInt # numEltSum1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) CInt -> Array n CInt # numEltProduct1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) CInt -> Array n CInt # numEltSumFull :: forall (n :: Nat). SNat n -> Array n CInt -> CInt # numEltProductFull :: forall (n :: Nat). SNat n -> Array n CInt -> CInt # numEltMinIndex :: forall (n :: Nat). SNat n -> Array n CInt -> [Int] # numEltMaxIndex :: forall (n :: Nat). SNat n -> Array n CInt -> [Int] # numEltDotprodInner :: forall (n :: Nat). SNat n -> Array (n + 1) CInt -> Array (n + 1) CInt -> Array n CInt # | |
NumElt Int32 | |
Defined in Data.Array.Strided.Arith.Internal Methods numEltAdd :: forall (n :: Nat). SNat n -> Array n Int32 -> Array n Int32 -> Array n Int32 # numEltSub :: forall (n :: Nat). SNat n -> Array n Int32 -> Array n Int32 -> Array n Int32 # numEltMul :: forall (n :: Nat). SNat n -> Array n Int32 -> Array n Int32 -> Array n Int32 # numEltNeg :: forall (n :: Nat). SNat n -> Array n Int32 -> Array n Int32 # numEltAbs :: forall (n :: Nat). SNat n -> Array n Int32 -> Array n Int32 # numEltSignum :: forall (n :: Nat). SNat n -> Array n Int32 -> Array n Int32 # numEltSum1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Int32 -> Array n Int32 # numEltProduct1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Int32 -> Array n Int32 # numEltSumFull :: forall (n :: Nat). SNat n -> Array n Int32 -> Int32 # numEltProductFull :: forall (n :: Nat). SNat n -> Array n Int32 -> Int32 # numEltMinIndex :: forall (n :: Nat). SNat n -> Array n Int32 -> [Int] # numEltMaxIndex :: forall (n :: Nat). SNat n -> Array n Int32 -> [Int] # numEltDotprodInner :: forall (n :: Nat). SNat n -> Array (n + 1) Int32 -> Array (n + 1) Int32 -> Array n Int32 # | |
NumElt Int64 | |
Defined in Data.Array.Strided.Arith.Internal Methods numEltAdd :: forall (n :: Nat). SNat n -> Array n Int64 -> Array n Int64 -> Array n Int64 # numEltSub :: forall (n :: Nat). SNat n -> Array n Int64 -> Array n Int64 -> Array n Int64 # numEltMul :: forall (n :: Nat). SNat n -> Array n Int64 -> Array n Int64 -> Array n Int64 # numEltNeg :: forall (n :: Nat). SNat n -> Array n Int64 -> Array n Int64 # numEltAbs :: forall (n :: Nat). SNat n -> Array n Int64 -> Array n Int64 # numEltSignum :: forall (n :: Nat). SNat n -> Array n Int64 -> Array n Int64 # numEltSum1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Int64 -> Array n Int64 # numEltProduct1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Int64 -> Array n Int64 # numEltSumFull :: forall (n :: Nat). SNat n -> Array n Int64 -> Int64 # numEltProductFull :: forall (n :: Nat). SNat n -> Array n Int64 -> Int64 # numEltMinIndex :: forall (n :: Nat). SNat n -> Array n Int64 -> [Int] # numEltMaxIndex :: forall (n :: Nat). SNat n -> Array n Int64 -> [Int] # numEltDotprodInner :: forall (n :: Nat). SNat n -> Array (n + 1) Int64 -> Array (n + 1) Int64 -> Array n Int64 # | |
NumElt Double | |
Defined in Data.Array.Strided.Arith.Internal Methods numEltAdd :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # numEltSub :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # numEltMul :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # numEltNeg :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # numEltAbs :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # numEltSignum :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # numEltSum1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Double -> Array n Double # numEltProduct1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Double -> Array n Double # numEltSumFull :: forall (n :: Nat). SNat n -> Array n Double -> Double # numEltProductFull :: forall (n :: Nat). SNat n -> Array n Double -> Double # numEltMinIndex :: forall (n :: Nat). SNat n -> Array n Double -> [Int] # numEltMaxIndex :: forall (n :: Nat). SNat n -> Array n Double -> [Int] # numEltDotprodInner :: forall (n :: Nat). SNat n -> Array (n + 1) Double -> Array (n + 1) Double -> Array n Double # | |
NumElt Float | |
Defined in Data.Array.Strided.Arith.Internal Methods numEltAdd :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # numEltSub :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # numEltMul :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # numEltNeg :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # numEltAbs :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # numEltSignum :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # numEltSum1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Float -> Array n Float # numEltProduct1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Float -> Array n Float # numEltSumFull :: forall (n :: Nat). SNat n -> Array n Float -> Float # numEltProductFull :: forall (n :: Nat). SNat n -> Array n Float -> Float # numEltMinIndex :: forall (n :: Nat). SNat n -> Array n Float -> [Int] # numEltMaxIndex :: forall (n :: Nat). SNat n -> Array n Float -> [Int] # numEltDotprodInner :: forall (n :: Nat). SNat n -> Array (n + 1) Float -> Array (n + 1) Float -> Array n Float # | |
NumElt Int | |
Defined in Data.Array.Strided.Arith.Internal Methods numEltAdd :: forall (n :: Nat). SNat n -> Array n Int -> Array n Int -> Array n Int # numEltSub :: forall (n :: Nat). SNat n -> Array n Int -> Array n Int -> Array n Int # numEltMul :: forall (n :: Nat). SNat n -> Array n Int -> Array n Int -> Array n Int # numEltNeg :: forall (n :: Nat). SNat n -> Array n Int -> Array n Int # numEltAbs :: forall (n :: Nat). SNat n -> Array n Int -> Array n Int # numEltSignum :: forall (n :: Nat). SNat n -> Array n Int -> Array n Int # numEltSum1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Int -> Array n Int # numEltProduct1Inner :: forall (n :: Nat). SNat n -> Array (n + 1) Int -> Array n Int # numEltSumFull :: forall (n :: Nat). SNat n -> Array n Int -> Int # numEltProductFull :: forall (n :: Nat). SNat n -> Array n Int -> Int # numEltMinIndex :: forall (n :: Nat). SNat n -> Array n Int -> [Int] # numEltMaxIndex :: forall (n :: Nat). SNat n -> Array n Int -> [Int] # numEltDotprodInner :: forall (n :: Nat). SNat n -> Array (n + 1) Int -> Array (n + 1) Int -> Array n Int # |
class NumElt a => FloatElt a #
Minimal complete definition
floatEltDiv, floatEltPow, floatEltLogbase, floatEltRecip, floatEltExp, floatEltLog, floatEltSqrt, floatEltSin, floatEltCos, floatEltTan, floatEltAsin, floatEltAcos, floatEltAtan, floatEltSinh, floatEltCosh, floatEltTanh, floatEltAsinh, floatEltAcosh, floatEltAtanh, floatEltLog1p, floatEltExpm1, floatEltLog1pexp, floatEltLog1mexp, floatEltAtan2
Instances
FloatElt Double | |
Defined in Data.Array.Strided.Arith.Internal Methods floatEltDiv :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # floatEltPow :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # floatEltLogbase :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # floatEltRecip :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltExp :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltLog :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltSqrt :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltSin :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltCos :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltTan :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAsin :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAcos :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAtan :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltSinh :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltCosh :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltTanh :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAsinh :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAcosh :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAtanh :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltLog1p :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltExpm1 :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltLog1pexp :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltLog1mexp :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double # floatEltAtan2 :: forall (n :: Nat). SNat n -> Array n Double -> Array n Double -> Array n Double # | |
FloatElt Float | |
Defined in Data.Array.Strided.Arith.Internal Methods floatEltDiv :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # floatEltPow :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # floatEltLogbase :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # floatEltRecip :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltExp :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltLog :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltSqrt :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltSin :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltCos :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltTan :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAsin :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAcos :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAtan :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltSinh :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltCosh :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltTanh :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAsinh :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAcosh :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAtanh :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltLog1p :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltExpm1 :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltLog1pexp :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltLog1mexp :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float # floatEltAtan2 :: forall (n :: Nat). SNat n -> Array n Float -> Array n Float -> Array n Float # |
type family Rank (sh :: [a]) :: Natural where ... Source #
The length of a type-level list. If the argument is a shape, then the result is the rank of that shape.