aboutsummaryrefslogtreecommitdiff
path: root/src/Data/Array/Nested/Shaped
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Array/Nested/Shaped')
-rw-r--r--src/Data/Array/Nested/Shaped/Shape.hs13
1 files changed, 3 insertions, 10 deletions
diff --git a/src/Data/Array/Nested/Shaped/Shape.hs b/src/Data/Array/Nested/Shaped/Shape.hs
index 2a12cce..9d463a9 100644
--- a/src/Data/Array/Nested/Shaped/Shape.hs
+++ b/src/Data/Array/Nested/Shaped/Shape.hs
@@ -1,10 +1,9 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
-{-# LANGUAGE DeriveGeneric #-}
-{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoStarIsType #-}
@@ -39,7 +38,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
@@ -216,7 +214,7 @@ listsPermutePrefix perm sh = listsAppend (listsPermute perm (listsTakeLenPerm pe
type role IxS nominal representational
type IxS :: [Nat] -> Type -> Type
newtype IxS sh i = IxS (ListS sh (Const i))
- deriving (Eq, Ord, Generic)
+ deriving (Eq, Ord, NFData)
pattern ZIS :: forall sh i. () => sh ~ '[] => IxS sh i
pattern ZIS = IxS ZS
@@ -258,8 +256,6 @@ instance Foldable (IxS sh) where
null ZIS = False
null _ = True
-instance NFData i => NFData (IxS sh i)
-
ixsLength :: IxS sh i -> Int
ixsLength (IxS l) = listsLength l
@@ -332,7 +328,7 @@ ixsToLinear = \sh i -> go sh i 0
type role ShS nominal
type ShS :: [Nat] -> Type
newtype ShS sh = ShS (ShX (MapJust sh) Int)
- deriving (Generic)
+ deriving (NFData)
instance Eq (ShS sh) where _ == _ = True
instance Ord (ShS sh) where compare _ _ = EQ
@@ -371,9 +367,6 @@ instance Show (ShS sh) where
showsPrec d (ShS shx) = showsPrec d shx
#endif
-instance NFData (ShS sh) where
- rnf (ShS shx) = rnf shx
-
instance TestEquality ShS where
testEquality (ShS shx1) (ShS shx2) = case shxEqType shx1 shx2 of
Nothing -> Nothing