diff options
Diffstat (limited to 'src/Data/Array/Nested/Shaped')
| -rw-r--r-- | src/Data/Array/Nested/Shaped/Base.hs | 9 | ||||
| -rw-r--r-- | src/Data/Array/Nested/Shaped/Shape.hs | 13 | 
2 files changed, 22 insertions, 0 deletions
| diff --git a/src/Data/Array/Nested/Shaped/Base.hs b/src/Data/Array/Nested/Shaped/Base.hs index 74c231d..8f41455 100644 --- a/src/Data/Array/Nested/Shaped/Base.hs +++ b/src/Data/Array/Nested/Shaped/Base.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-}  {-# LANGUAGE DataKinds #-}  {-# LANGUAGE DeriveGeneric #-}  {-# LANGUAGE FlexibleContexts #-} @@ -49,13 +50,18 @@ import Data.Array.Strided.Arith  -- 'Shaped' is a newtype around a 'Mixed' of 'Just's.  type Shaped :: [Nat] -> Type -> Type  newtype Shaped sh a = Shaped (Mixed (MapJust sh) a) +#ifdef OXAR_DEFAULT_SHOW_INSTANCES +deriving instance Show (Mixed (MapJust sh) a) => Show (Shaped sh a) +#endif  deriving instance Eq (Mixed (MapJust sh) a) => Eq (Shaped sh a)  deriving instance Ord (Mixed (MapJust sh) a) => Ord (Shaped sh a) +#ifndef OXAR_DEFAULT_SHOW_INSTANCES  instance (Show a, Elt a) => Show (Shaped n a) where    showsPrec d arr@(Shaped marr) =      let sh = show (shsToList (sshape arr))      in showsMixedArray ("sfromListLinear " ++ sh) ("sreplicate " ++ sh) d marr +#endif  instance Elt a => NFData (Shaped sh a) where    rnf (Shaped arr) = rnf arr @@ -63,6 +69,9 @@ instance Elt a => NFData (Shaped sh a) where  -- just unwrap the newtype and defer to the general instance for nested arrays  newtype instance Mixed sh (Shaped sh' a) = M_Shaped (Mixed sh (Mixed (MapJust sh') a))    deriving (Generic) +#ifdef OXAR_DEFAULT_SHOW_INSTANCES +deriving instance Show (Mixed sh (Mixed (MapJust sh') a)) => Show (Mixed sh (Shaped sh' a)) +#endif  deriving instance Eq (Mixed sh (Mixed (MapJust sh') a)) => Eq (Mixed sh (Shaped sh' a)) diff --git a/src/Data/Array/Nested/Shaped/Shape.hs b/src/Data/Array/Nested/Shaped/Shape.hs index 092465f..59a7d61 100644 --- a/src/Data/Array/Nested/Shaped/Shape.hs +++ b/src/Data/Array/Nested/Shaped/Shape.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-}  {-# LANGUAGE DataKinds #-}  {-# LANGUAGE DeriveFoldable #-}  {-# LANGUAGE DeriveFunctor #-} @@ -58,8 +59,12 @@ deriving instance (forall n. Eq (f n)) => Eq (ListS sh f)  deriving instance (forall n. Ord (f n)) => Ord (ListS sh f)  infixr 3 ::$ +#ifdef OXAR_DEFAULT_SHOW_INSTANCES +deriving instance (forall n. Show (f n)) => Show (ListS sh f) +#else  instance (forall n. Show (f n)) => Show (ListS sh f) where    showsPrec _ = listsShow shows +#endif  instance (forall m. NFData (f m)) => NFData (ListS n f) where    rnf ZS = () @@ -201,8 +206,12 @@ infixr 3 :.$  type IIxS sh = IxS sh Int +#ifdef OXAR_DEFAULT_SHOW_INSTANCES +deriving instance Show i => Show (IxS sh i) +#else  instance Show i => Show (IxS sh i) where    showsPrec _ (IxS l) = listsShow (\(Const i) -> shows i) l +#endif  instance Functor (IxS sh) where    fmap f (IxS l) = IxS (listsFmap (Const . f . getConst) l) @@ -280,8 +289,12 @@ infixr 3 :$$  {-# COMPLETE ZSS, (:$$) #-} +#ifdef OXAR_DEFAULT_SHOW_INSTANCES +deriving instance Show (ShS sh) +#else  instance Show (ShS sh) where    showsPrec _ (ShS l) = listsShow (shows . fromSNat) l +#endif  instance NFData (ShS sh) where    rnf (ShS ZS) = () | 
