aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Array/Nested/Mixed.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Array/Nested/Mixed.hs')
-rw-r--r--src/Data/Array/Nested/Mixed.hs7
1 files changed, 7 insertions, 0 deletions
diff --git a/src/Data/Array/Nested/Mixed.hs b/src/Data/Array/Nested/Mixed.hs
index 144230e..4028b1d 100644
--- a/src/Data/Array/Nested/Mixed.hs
+++ b/src/Data/Array/Nested/Mixed.hs
@@ -5,6 +5,7 @@
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GADTs #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE RankNTypes #-}
@@ -287,6 +288,8 @@ mremArray = mliftNumElt2 (liftO2 . intEltRem)
matan2Array :: (FloatElt a, PrimElt a) => Mixed sh a -> Mixed sh a -> Mixed sh a
matan2Array = mliftNumElt2 (liftO2 . floatEltAtan2)
+type MRepTrans = RepTrans (SMayNat Int SNat)
+
-- | Allowable element types in a mixed array, and by extension in a 'Ranked' or
-- 'Shaped' array. Note the polymorphic instance for 'Elt' of @'Primitive'
-- a@; see the documentation for 'Primitive' for more details.
@@ -340,6 +343,8 @@ class Elt a where
mtranspose :: forall is sh. (IsPermutation is, Rank is <= Rank sh)
=> Perm is -> Mixed sh a -> Mixed (PermutePrefix is sh) a
+ mreptransPartial :: Proxy sh' -> MRepTrans sh1 sh2 -> Mixed (sh1 ++ sh') a -> Mixed (sh2 ++ sh') a
+
-- | All arrays in the input must have equal shapes, including subarrays
-- inside their elements.
mconcat :: NonEmpty (Mixed (Nothing : sh) a) -> Mixed (Nothing : sh) a
@@ -445,6 +450,8 @@ instance Storable a => Elt (Primitive a) where
M_Primitive (shxPermutePrefix perm sh)
(X.transpose (ssxFromShX sh) perm arr)
+ mreptransPartial p descr (M_Primitive sh arr) = _
+
mconcat :: forall sh. NonEmpty (Mixed (Nothing : sh) (Primitive a)) -> Mixed (Nothing : sh) (Primitive a)
mconcat l@(M_Primitive (_ :$% sh) _ :| _) =
let result = X.concat (ssxFromShX sh) (fmap (\(M_Primitive _ arr) -> arr) l)