diff options
Diffstat (limited to 'src/Data')
| -rw-r--r-- | src/Data/Array/Mixed.hs | 1 | ||||
| -rw-r--r-- | src/Data/Array/Nested/Internal.hs | 12 | 
2 files changed, 13 insertions, 0 deletions
| diff --git a/src/Data/Array/Mixed.hs b/src/Data/Array/Mixed.hs index 30dfd92..f597bbf 100644 --- a/src/Data/Array/Mixed.hs +++ b/src/Data/Array/Mixed.hs @@ -70,6 +70,7 @@ type family Rank sh where  type XArray :: [Maybe Nat] -> Type -> Type  data XArray sh a = XArray (U.Array (GNat (Rank sh)) a) +  deriving (Show)  zeroIdx :: StaticShapeX sh -> IxX sh  zeroIdx SZX = IZX diff --git a/src/Data/Array/Nested/Internal.hs b/src/Data/Array/Nested/Internal.hs index 892f4d8..7d4621a 100644 --- a/src/Data/Array/Nested/Internal.hs +++ b/src/Data/Array/Nested/Internal.hs @@ -1,6 +1,7 @@  {-# LANGUAGE DataKinds #-}  {-# LANGUAGE DerivingVia #-}  {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-}  {-# LANGUAGE GADTs #-}  {-# LANGUAGE InstanceSigs #-}  {-# LANGUAGE PolyKinds #-} @@ -12,6 +13,7 @@  {-# LANGUAGE TypeApplications #-}  {-# LANGUAGE TypeFamilies #-}  {-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-}  {-|  TODO: @@ -91,16 +93,22 @@ type Mixed :: [Maybe Nat] -> Type -> Type  data family Mixed sh a  newtype instance Mixed sh (Primitive a) = M_Primitive (XArray sh a) +  deriving (Show)  newtype instance Mixed sh Int = M_Int (XArray sh Int) +  deriving (Show)  newtype instance Mixed sh Double = M_Double (XArray sh Double) +  deriving (Show)  newtype instance Mixed sh () = M_Nil (XArray sh ())  -- no content, orthotope optimises this (via Vector) +  deriving (Show)  -- etc.  data instance Mixed sh (a, b) = M_Tup2 (Mixed sh a) (Mixed sh b) +deriving instance (Show (Mixed sh a), Show (Mixed sh b)) => Show (Mixed sh (a, b))  -- etc.  newtype instance Mixed sh1 (Mixed sh2 a) = M_Nest (Mixed (sh1 ++ sh2) a) +deriving instance Show (Mixed (sh1 ++ sh2) a) => Show (Mixed sh1 (Mixed sh2 a))  -- | Internal helper data family mirrorring 'Mixed' that consists of mutable @@ -322,6 +330,7 @@ mgenerate sh f  -- 'Ranked' is a newtype around a 'Mixed' of 'Nothing's.  type Ranked :: Nat -> Type -> Type  newtype Ranked n a = Ranked (Mixed (Replicate n Nothing) a) +deriving instance Show (Mixed (Replicate n Nothing) a) => Show (Ranked n a)  -- | 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. @@ -332,10 +341,13 @@ newtype Ranked n a = Ranked (Mixed (Replicate n Nothing) a)  -- 'Shaped' is a newtype around a 'Mixed' of 'Just's.  type Shaped :: [Nat] -> Type -> Type  newtype Shaped sh a = Shaped (Mixed (MapJust sh) a) +deriving instance Show (Mixed (MapJust sh) a) => Show (Shaped sh a)  -- just unwrap the newtype and defer to the general instance for nested arrays  newtype instance Mixed sh (Ranked n   a) = M_Ranked (Mixed sh (Mixed (Replicate n Nothing) a)) +deriving instance Show (Mixed sh (Mixed (Replicate n Nothing) a)) => Show (Mixed sh (Ranked n a))  newtype instance Mixed sh (Shaped sh' a) = M_Shaped (Mixed sh (Mixed (MapJust sh'        ) a)) +deriving instance Show (Mixed sh (Mixed (MapJust sh'        ) a)) => Show (Mixed sh (Shaped sh' a))  newtype instance MixedVecs s sh (Ranked n   a) = MV_Ranked (MixedVecs s sh (Mixed (Replicate n Nothing) a))  newtype instance MixedVecs s sh (Shaped sh' a) = MV_Shaped (MixedVecs s sh (Mixed (MapJust sh'        ) a)) | 
