aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Array/Nested/Mixed
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Array/Nested/Mixed')
-rw-r--r--src/Data/Array/Nested/Mixed/Shape.hs21
1 files changed, 4 insertions, 17 deletions
diff --git a/src/Data/Array/Nested/Mixed/Shape.hs b/src/Data/Array/Nested/Mixed/Shape.hs
index 6b7708f..1071859 100644
--- a/src/Data/Array/Nested/Mixed/Shape.hs
+++ b/src/Data/Array/Nested/Mixed/Shape.hs
@@ -1,10 +1,10 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoStarIsType #-}
@@ -39,7 +39,6 @@ import Data.Monoid (Sum(..))
import Data.Proxy
import Data.Type.Equality
import GHC.Exts (Int(..), Int#, build, quotRemInt#, withDict)
-import GHC.Generics (Generic)
import GHC.IsList (IsList)
import GHC.IsList qualified as IsList
import GHC.TypeLits
@@ -191,7 +190,7 @@ listxZipWith f (i ::% is) (j ::% js) = f i j ::% listxZipWith f is js
type role IxX nominal representational
type IxX :: [Maybe Nat] -> Type -> Type
newtype IxX sh i = IxX (ListX sh (Const i))
- deriving (Eq, Ord, Generic)
+ deriving (Eq, Ord, NFData)
pattern ZIX :: forall sh i. () => sh ~ '[] => IxX sh i
pattern ZIX = IxX ZX
@@ -231,8 +230,6 @@ instance Foldable (IxX sh) where
null ZIX = False
null _ = True
-instance NFData i => NFData (IxX sh i)
-
ixxLength :: IxX sh i -> Int
ixxLength (IxX l) = listxLength l
@@ -468,7 +465,7 @@ listhLast (x `ConsKnown` ZH) = SKnown x
type role ShX nominal representational
type ShX :: [Maybe Nat] -> Type -> Type
newtype ShX sh i = ShX (ListH sh i)
- deriving (Eq, Ord, Generic)
+ deriving (Eq, Ord, NFData)
pattern ZSX :: forall sh i. () => sh ~ '[] => ShX sh i
pattern ZSX = ShX ZH
@@ -496,11 +493,6 @@ instance Functor (ShX sh) where
{-# INLINE fmap #-}
fmap f (ShX l) = ShX (listhFmap (fromSMayNat (SUnknown . f) SKnown) l)
-instance NFData i => NFData (ShX sh i) where
- rnf (ShX ZH) = ()
- rnf (ShX (i `ConsUnknown` l)) = rnf i `seq` rnf (ShX l)
- rnf (ShX (SNat `ConsKnown` l)) = rnf (ShX l)
-
-- | This checks only whether the types are equal; unknown dimensions might
-- still differ. This corresponds to 'testEquality', except on the penultimate
-- type parameter.
@@ -658,7 +650,7 @@ shxCast' ssh sh = case shxCast ssh sh of
-- | The part of a shape that is statically known. (A newtype over 'ListH'.)
type StaticShX :: [Maybe Nat] -> Type
newtype StaticShX sh = StaticShX (ListH sh ())
- deriving (Eq, Ord)
+ deriving (Eq, Ord, NFData)
pattern ZKX :: forall sh. () => sh ~ '[] => StaticShX sh
pattern ZKX = StaticShX ZH
@@ -681,11 +673,6 @@ instance Show (StaticShX sh) where
showsPrec _ (StaticShX l) = listhShow (fromSMayNat shows (shows . fromSNat)) l
#endif
-instance NFData (StaticShX sh) where
- rnf (StaticShX ZH) = ()
- rnf (StaticShX (() `ConsUnknown` l)) = rnf (StaticShX l)
- rnf (StaticShX (SNat `ConsKnown` l)) = rnf (StaticShX l)
-
instance TestEquality StaticShX where
testEquality (StaticShX l1) (StaticShX l2) = listhEqType l1 l2