aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Array
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Array')
-rw-r--r--src/Data/Array/Mixed.hs28
-rw-r--r--src/Data/Array/Nested/Internal.hs34
2 files changed, 30 insertions, 32 deletions
diff --git a/src/Data/Array/Mixed.hs b/src/Data/Array/Mixed.hs
index fa61b01..6ac3ab3 100644
--- a/src/Data/Array/Mixed.hs
+++ b/src/Data/Array/Mixed.hs
@@ -28,6 +28,7 @@ import qualified Data.Array.RankedS as S
import qualified Data.Array.Ranked as ORB
import Data.Bifunctor (first)
import Data.Coerce
+import qualified Data.Foldable as Foldable
import Data.Functor.Const
import Data.Kind
import Data.Monoid (Sum(..))
@@ -36,7 +37,8 @@ import Data.Type.Bool
import Data.Type.Equality
import qualified Data.Vector.Storable as VS
import Foreign.Storable (Storable)
-import GHC.IsList
+import GHC.IsList (IsList)
+import qualified GHC.IsList as IsList
import GHC.TypeError
import GHC.TypeLits
import qualified GHC.TypeNats as TypeNats
@@ -125,6 +127,10 @@ showListX f l = showString "[" . go "" l . showString "]"
go _ ZX = id
go prefix (x ::% xs) = showString prefix . f x . go "," xs
+listXToList :: ListX sh' (Const i) -> [i]
+listXToList ZX = []
+listXToList (Const i ::% is) = i : listXToList is
+
type role IxX nominal representational
type IxX :: [Maybe Nat] -> Type -> Type
@@ -199,6 +205,10 @@ instance Functor (ShX sh) where
lengthShX :: ShX sh i -> Int
lengthShX (ShX l) = lengthListX l
+shXToList :: IShX sh -> [Int]
+shXToList ZSX = []
+shXToList (smn :$% sh) = fromSMayNat' smn : shXToList sh
+
-- | The part of a shape that is statically known.
type StaticShX :: [Maybe Nat] -> Type
@@ -245,17 +255,13 @@ instance KnownShX sh => IsList (ListX sh (Const i)) where
go _ _ = error $ "IsList(ListX): Mismatched list length (type says "
++ show (lengthStaticShX (knownShX @sh)) ++ ", list has length "
++ show (length topl) ++ ")"
- toList = go
- where
- go :: ListX sh' (Const i) -> [i]
- go ZX = []
- go (Const i ::% is) = i : go is
+ toList = listXToList
-- | Very untyped: only length is checked (at runtime), index bounds are __not checked__.
instance KnownShX sh => IsList (IxX sh i) where
type Item (IxX sh i) = i
- fromList = IxX . fromList
- toList (IxX l) = toList l
+ fromList = IxX . IsList.fromList
+ toList = Foldable.toList
-- | Untyped: length and known dimensions are checked (at runtime).
instance KnownShX sh => IsList (ShX sh Int) where
@@ -272,11 +278,7 @@ instance KnownShX sh => IsList (ShX sh Int) where
go _ _ = error $ "IsList(ShX): Mismatched list length (type says "
++ show (lengthStaticShX (knownShX @sh)) ++ ", list has length "
++ show (length topl) ++ ")"
- toList = go
- where
- go :: ShX sh' Int -> [Int]
- go ZSX = []
- go (smn :$% sh) = fromSMayNat' smn : go sh
+ toList = shXToList
type family Rank sh where
diff --git a/src/Data/Array/Nested/Internal.hs b/src/Data/Array/Nested/Internal.hs
index 19e6545..ab5f015 100644
--- a/src/Data/Array/Nested/Internal.hs
+++ b/src/Data/Array/Nested/Internal.hs
@@ -43,7 +43,7 @@ import Control.Monad.ST
import qualified Data.Array.RankedS as S
import Data.Bifunctor (first)
import Data.Coerce (coerce, Coercible)
-import Data.Foldable (toList)
+import Data.Foldable as Foldable (toList)
import Data.Functor.Const
import Data.Kind
import Data.List.NonEmpty (NonEmpty(..))
@@ -241,23 +241,19 @@ instance KnownNat n => IsList (ListR n i) where
go SZ [] = ZR
go (SS n) (i : is) = i ::: go n is
go _ _ = error "IsList(ListR): Mismatched list length"
- toList = go
- where
- go :: ListR n' i -> [i]
- go ZR = []
- go (i ::: is) = i : go is
+ toList = Foldable.toList
-- | Untyped: length is checked at runtime.
instance KnownNat n => IsList (IxR n i) where
type Item (IxR n i) = i
fromList = IxR . IsList.fromList
- toList (IxR idx) = IsList.toList idx
+ toList = Foldable.toList
-- | Untyped: length is checked at runtime.
instance KnownNat n => IsList (ShR n i) where
type Item (ShR n i) = i
fromList = ShR . IsList.fromList
- toList (ShR idx) = IsList.toList idx
+ toList = Foldable.toList
type role ListS nominal representational
@@ -293,6 +289,10 @@ showListS f l = showString "[" . go "" l . showString "]"
go _ ZS = id
go prefix (x ::$ xs) = showString prefix . f x . go "," xs
+listSToList :: ListS sh (Const i) -> [i]
+listSToList ZS = []
+listSToList (Const i ::$ is) = i : listSToList is
+
-- | An index into a shape-typed array.
--
@@ -356,6 +356,10 @@ instance Show (ShS sh) where
lengthShS :: ShS sh -> Int
lengthShS (ShS l) = getSum (foldListS (\_ -> Sum 1) l)
+shSToList :: ShS sh -> [Int]
+shSToList ZSS = []
+shSToList (sn :$$ sh) = fromSNat' sn : shSToList sh
+
-- | Untyped: length is checked at runtime.
instance KnownShS sh => IsList (ListS sh (Const i)) where
@@ -368,17 +372,13 @@ instance KnownShS sh => IsList (ListS sh (Const i)) where
go _ _ = error $ "IsList(ListS): Mismatched list length (type says "
++ show (lengthShS (knownShS @sh)) ++ ", list has length "
++ show (length topl) ++ ")"
- toList = go
- where
- go :: ListS sh' (Const i) -> [i]
- go ZS = []
- go (Const i ::$ is) = i : go is
+ toList = listSToList
-- | Very untyped: only length is checked (at runtime), index bounds are __not checked__.
instance KnownShS sh => IsList (IxS sh i) where
type Item (IxS sh i) = i
fromList = IxS . IsList.fromList
- toList (IxS idx) = IsList.toList idx
+ toList = Foldable.toList
-- | Untyped: length and values are checked at runtime.
instance KnownShS sh => IsList (ShS sh) where
@@ -394,11 +394,7 @@ instance KnownShS sh => IsList (ShS sh) where
go _ _ = error $ "IsList(ShS): Mismatched list length (type says "
++ show (lengthShS (knownShS @sh)) ++ ", list has length "
++ show (length topl) ++ ")"
- toList = go
- where
- go :: ShS sh' -> [Int]
- go ZSS = []
- go (sn :$$ sh) = fromSNat' sn : go sh
+ toList = shSToList
-- | Wrapper type used as a tag to attach instances on. The instances on arrays