diff --git a/.git-blame-ignore-revs b/.git-blame-ignore-revs new file mode 100644 index 0000000..da8ad41 --- /dev/null +++ b/.git-blame-ignore-revs @@ -0,0 +1 @@ +17a9895f94d3e86c55ee4a57affdf0b15db39aab diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml index 75d433b..6e57d7e 100644 --- a/.github/workflows/ci.yml +++ b/.github/workflows/ci.yml @@ -48,25 +48,15 @@ jobs: compilerVersion: 8.10.7 setup-method: ghcup allow-failure: false - - compiler: ghc-8.6.5 - compilerKind: ghc - compilerVersion: 8.6.5 - setup-method: hvr-ppa - allow-failure: false - - compiler: ghc-8.4.4 - compilerKind: ghc - compilerVersion: 8.4.4 - setup-method: hvr-ppa - allow-failure: false - - compiler: ghc-8.2.2 + - compiler: ghc-8.8.4 compilerKind: ghc - compilerVersion: 8.2.2 - setup-method: hvr-ppa + compilerVersion: 8.8.4 + setup-method: ghcup allow-failure: false - - compiler: ghc-8.0.2 + - compiler: ghc-8.6.5 compilerKind: ghc - compilerVersion: 8.0.2 - setup-method: hvr-ppa + compilerVersion: 8.6.5 + setup-method: ghcup allow-failure: false fail-fast: false steps: diff --git a/Control/DeepSeq.hs b/Control/DeepSeq.hs index 30bd481..c79bd5e 100644 --- a/Control/DeepSeq.hs +++ b/Control/DeepSeq.hs @@ -1,29 +1,22 @@ -{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DefaultSignatures #-} +{-# LANGUAGE EmptyCase #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE Safe #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} -{-# LANGUAGE PolyKinds #-} -{-# LANGUAGE EmptyCase #-} - -#if MIN_VERSION_base(4,12,0) -{-# LANGUAGE QuantifiedConstraints #-} -#endif #if __GLASGOW_HASKELL__ >= 811 && __GLASGOW_HASKELL__ < 901 -- For the Option instance (https://gitlab.haskell.org/ghc/ghc/issues/15028) {-# OPTIONS_GHC -Wno-deprecations #-} #endif -#define BYTEARRAY_IN_BASE (__GLASGOW_HASKELL__ >= 903) --- At the moment of writing GHC source tree has not yet bumped `base` version, --- so using __GLASGOW_HASKELL__ as a proxy instead of MIN_VERSION_base(4,17,0). - ----------------------------------------------------------------------------- + -- | -- Module : Control.DeepSeq -- Copyright : (c) The University of Glasgow 2001-2009 @@ -76,65 +69,61 @@ -- -- @since 1.1.0.0 module Control.DeepSeq ( - -- * 'NFData' class - NFData(rnf), - -- * Helper functions - deepseq, - force, - ($!!), - (<$!!>), - rwhnf, - - -- * Liftings of the 'NFData' class - -- ** For unary constructors - NFData1(liftRnf), rnf1, - -- ** For binary constructors - NFData2(liftRnf2), rnf2, - ) where + -- * 'NFData' class + NFData (rnf), -import Control.Applicative -import Control.Concurrent ( ThreadId, MVar ) -import Control.Exception ( MaskingState(..) ) -import Data.IORef -import Data.STRef -import Data.Int -import Data.Word -import Data.Ratio -import Data.Complex -import Data.Array -import Data.Fixed -import Data.Version -import Data.Monoid as Mon -import Data.Typeable ( TypeRep, rnfTypeRep, TyCon, rnfTyCon ) -import Data.Unique ( Unique ) -import Foreign.Ptr -import Foreign.C.Types -import System.Exit ( ExitCode(..) ) -import System.Mem.StableName ( StableName ) -import Data.Ord ( Down(Down) ) -import Data.Proxy ( Proxy(Proxy) ) + -- * Helper functions + deepseq, + force, + ($!!), + (<$!!>), + rwhnf, -#if MIN_VERSION_base(4,10,0) -import Data.Type.Equality ( (:~:), (:~~:) ) -import qualified Type.Reflection as Reflection -#else -import Data.Type.Equality ( (:~:) ) -#endif + -- * Liftings of the 'NFData' class -import Data.Functor.Identity ( Identity(..) ) -import Data.Void ( Void, absurd ) -import Numeric.Natural ( Natural ) + -- ** For unary constructors + NFData1 (liftRnf), + rnf1, -import Data.List.NonEmpty ( NonEmpty (..) ) -import Data.Semigroup as Semi + -- ** For binary constructors + NFData2 (liftRnf2), + rnf2, +) where -import GHC.Stack.Types ( CallStack(..), SrcLoc(..) ) +import Control.Applicative +import Control.Concurrent (MVar, ThreadId) +import Control.Exception (MaskingState (..)) +import Data.Array +import Data.Complex +import Data.Fixed import Data.Functor.Compose -import qualified Data.Functor.Sum as Functor +import Data.Functor.Identity (Identity (..)) import qualified Data.Functor.Product as Functor - -import GHC.Fingerprint.Type ( Fingerprint(..) ) +import qualified Data.Functor.Sum as Functor +import Data.IORef +import Data.Int +import Data.List.NonEmpty (NonEmpty (..)) +import Data.Monoid as Mon +import Data.Ord (Down (Down)) +import Data.Proxy (Proxy (Proxy)) +import Data.Ratio +import Data.STRef +import Data.Semigroup as Semi +import Data.Type.Equality ((:~:), (:~~:)) +import Data.Typeable (TyCon, TypeRep, rnfTyCon, rnfTypeRep) +import Data.Unique (Unique) +import Data.Version +import Data.Void (Void, absurd) +import Data.Word +import Foreign.C.Types +import Foreign.Ptr +import GHC.Fingerprint.Type (Fingerprint (..)) import GHC.Generics +import GHC.Stack.Types (CallStack (..), SrcLoc (..)) +import Numeric.Natural (Natural) +import System.Exit (ExitCode (..)) +import System.Mem.StableName (StableName) +import qualified Type.Reflection as Reflection #ifdef MIN_VERSION_ghc_prim #if MIN_VERSION_ghc_prim(0,7,0) @@ -142,7 +131,7 @@ import GHC.Tuple (Solo (..)) #endif #endif -#if BYTEARRAY_IN_BASE +#if MIN_VERSION_base(4,17,0) import Data.Array.Byte (ByteArray(..), MutableByteArray(..)) #endif @@ -154,10 +143,13 @@ instance GNFData arity V1 where grnf _ x = case x of {} data Zero + data One data family RnfArgs arity a + data instance RnfArgs Zero a = RnfArgs0 + newtype instance RnfArgs One a = RnfArgs1 (a -> ()) instance GNFData arity U1 where @@ -173,8 +165,8 @@ instance GNFData arity a => GNFData arity (M1 i c a) where instance GNFData arity (URec a) where grnf _ = rwhnf -- Every URec data instance consists of a single data - -- constructor containing a single strict field, so reducing - -- any URec instance to WHNF suffices to reduce it to NF. + -- constructor containing a single strict field, so reducing + -- any URec instance to WHNF suffices to reduce it to NF. {-# INLINEABLE grnf #-} instance (GNFData arity a, GNFData arity b) => GNFData arity (a :*: b) where @@ -187,15 +179,16 @@ instance (GNFData arity a, GNFData arity b) => GNFData arity (a :+: b) where {-# INLINEABLE grnf #-} instance GNFData One Par1 where - grnf (RnfArgs1 r) = r . unPar1 + grnf (RnfArgs1 r) = r . unPar1 instance NFData1 f => GNFData One (Rec1 f) where - grnf (RnfArgs1 r) = liftRnf r . unRec1 + grnf (RnfArgs1 r) = liftRnf r . unRec1 instance (NFData1 f, GNFData One g) => GNFData One (f :.: g) where - grnf args = liftRnf (grnf args) . unComp1 + grnf args = liftRnf (grnf args) . unComp1 infixr 0 $!! + infixr 0 `deepseq` -- | 'deepseq': fully evaluates the first argument, before returning the @@ -271,14 +264,8 @@ force x = x `deepseq` x -- -- @since 1.4.3.0 (<$!!>) :: (Monad m, NFData b) => (a -> b) -> m a -> m b -#if MIN_VERSION_base(4,8,0) --- Minor optimisation for AMP; this avoids the redundant indirection --- through 'return' in case GHC isn't smart enough to optimise it away --- on its own f <$!!> m = m >>= \x -> pure $!! f x -#else -f <$!!> m = m >>= \x -> return $!! f x -#endif + infixl 4 <$!!> -- | Reduce to weak head normal form @@ -301,93 +288,88 @@ rwhnf = (`seq` ()) -- -- @since 1.1.0.0 class NFData a where - -- | 'rnf' should reduce its argument to normal form (that is, fully - -- evaluate all sub-components), and then return '()'. - -- - -- === 'Generic' 'NFData' deriving - -- - -- Starting with GHC 7.2, you can automatically derive instances - -- for types possessing a 'Generic' instance. - -- - -- Note: 'Generic1' can be auto-derived starting with GHC 7.4 - -- - -- > {-# LANGUAGE DeriveGeneric #-} - -- > - -- > import GHC.Generics (Generic, Generic1) - -- > import Control.DeepSeq - -- > - -- > data Foo a = Foo a String - -- > deriving (Eq, Generic, Generic1) - -- > - -- > instance NFData a => NFData (Foo a) - -- > instance NFData1 Foo - -- > - -- > data Colour = Red | Green | Blue - -- > deriving Generic - -- > - -- > instance NFData Colour - -- - -- Starting with GHC 7.10, the example above can be written more - -- concisely by enabling the new @DeriveAnyClass@ extension: - -- - -- > {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} - -- > - -- > import GHC.Generics (Generic) - -- > import Control.DeepSeq - -- > - -- > data Foo a = Foo a String - -- > deriving (Eq, Generic, Generic1, NFData, NFData1) - -- > - -- > data Colour = Red | Green | Blue - -- > deriving (Generic, NFData) - -- > - -- - -- === Compatibility with previous @deepseq@ versions - -- - -- Prior to version 1.4.0.0, the default implementation of the 'rnf' - -- method was defined as - -- - -- @'rnf' a = 'seq' a ()@ - -- - -- However, starting with @deepseq-1.4.0.0@, the default - -- implementation is based on @DefaultSignatures@ allowing for - -- more accurate auto-derived 'NFData' instances. If you need the - -- previously used exact default 'rnf' method implementation - -- semantics, use - -- - -- > instance NFData Colour where rnf x = seq x () - -- - -- or alternatively - -- - -- > instance NFData Colour where rnf = rwhnf - -- - -- or - -- - -- > {-# LANGUAGE BangPatterns #-} - -- > instance NFData Colour where rnf !_ = () - -- - rnf :: a -> () - - default rnf :: (Generic a, GNFData Zero (Rep a)) => a -> () - rnf = grnf RnfArgs0 . from + -- | 'rnf' should reduce its argument to normal form (that is, fully + -- evaluate all sub-components), and then return '()'. + -- + -- === 'Generic' 'NFData' deriving + -- + -- Starting with GHC 7.2, you can automatically derive instances + -- for types possessing a 'Generic' instance. + -- + -- Note: 'Generic1' can be auto-derived starting with GHC 7.4 + -- + -- > {-# LANGUAGE DeriveGeneric #-} + -- > + -- > import GHC.Generics (Generic, Generic1) + -- > import Control.DeepSeq + -- > + -- > data Foo a = Foo a String + -- > deriving (Eq, Generic, Generic1) + -- > + -- > instance NFData a => NFData (Foo a) + -- > instance NFData1 Foo + -- > + -- > data Colour = Red | Green | Blue + -- > deriving Generic + -- > + -- > instance NFData Colour + -- + -- Starting with GHC 7.10, the example above can be written more + -- concisely by enabling the new @DeriveAnyClass@ extension: + -- + -- > {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} + -- > + -- > import GHC.Generics (Generic) + -- > import Control.DeepSeq + -- > + -- > data Foo a = Foo a String + -- > deriving (Eq, Generic, Generic1, NFData, NFData1) + -- > + -- > data Colour = Red | Green | Blue + -- > deriving (Generic, NFData) + -- > + -- + -- === Compatibility with previous @deepseq@ versions + -- + -- Prior to version 1.4.0.0, the default implementation of the 'rnf' + -- method was defined as + -- + -- @'rnf' a = 'seq' a ()@ + -- + -- However, starting with @deepseq-1.4.0.0@, the default + -- implementation is based on @DefaultSignatures@ allowing for + -- more accurate auto-derived 'NFData' instances. If you need the + -- previously used exact default 'rnf' method implementation + -- semantics, use + -- + -- > instance NFData Colour where rnf x = seq x () + -- + -- or alternatively + -- + -- > instance NFData Colour where rnf = rwhnf + -- + -- or + -- + -- > {-# LANGUAGE BangPatterns #-} + -- > instance NFData Colour where rnf !_ = () + rnf :: a -> () + default rnf :: (Generic a, GNFData Zero (Rep a)) => a -> () + rnf = grnf RnfArgs0 . from -- | A class of functors that can be fully evaluated. -- +-- In `deepseq-1.5.0.0` this class was updated to include superclasses. +-- -- @since 1.4.3.0 -#if MIN_VERSION_base(4,12,0) class (forall a. NFData a => NFData (f a)) => NFData1 f where -#else -class NFData1 f where -#endif - -- | 'liftRnf' should reduce its argument to normal form (that is, fully - -- evaluate all sub-components), given an argument to reduce @a@ arguments, - -- and then return '()'. - -- - -- See 'rnf' for the generic deriving. - liftRnf :: (a -> ()) -> f a -> () - - default liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () - liftRnf r = grnf (RnfArgs1 r) . from1 + -- | 'liftRnf' should reduce its argument to normal form (that is, fully + -- evaluate all sub-components), given an argument to reduce @a@ arguments, + -- and then return '()'. + -- + -- See 'rnf' for the generic deriving. + liftRnf :: (a -> ()) -> f a -> () + default liftRnf :: (Generic1 f, GNFData One (Rep1 f)) => (a -> ()) -> f a -> () + liftRnf r = grnf (RnfArgs1 r) . from1 -- | Lift the standard 'rnf' function through the type constructor. -- @@ -397,19 +379,17 @@ rnf1 = liftRnf rnf -- | A class of bifunctors that can be fully evaluated. -- +-- In `deepseq-1.5.0.0` this class was updated to include superclasses. +-- -- @since 1.4.3.0 -#if MIN_VERSION_base(4,12,0) class (forall a. NFData a => NFData1 (p a)) => NFData2 p where -#else -class NFData2 p where -#endif - -- | 'liftRnf2' should reduce its argument to normal form (that - -- is, fully evaluate all sub-components), given functions to - -- reduce @a@ and @b@ arguments respectively, and then return '()'. - -- - -- __Note__: Unlike for the unary 'liftRnf', there is currently no - -- support for generically deriving 'liftRnf2'. - liftRnf2 :: (a -> ()) -> (b -> ()) -> p a b -> () + -- | 'liftRnf2' should reduce its argument to normal form (that + -- is, fully evaluate all sub-components), given functions to + -- reduce @a@ and @b@ arguments respectively, and then return '()'. + -- + -- __Note__: Unlike for the unary 'liftRnf', there is currently no + -- support for generically deriving 'liftRnf2'. + liftRnf2 :: (a -> ()) -> (b -> ()) -> p a b -> () -- | Lift the standard 'rnf' function through the type constructor. -- @@ -417,81 +397,97 @@ class NFData2 p where rnf2 :: (NFData2 p, NFData a, NFData b) => p a b -> () rnf2 = liftRnf2 rnf rnf +instance NFData Int where rnf = rwhnf -instance NFData Int where rnf = rwhnf -instance NFData Word where rnf = rwhnf -instance NFData Integer where rnf = rwhnf -instance NFData Float where rnf = rwhnf -instance NFData Double where rnf = rwhnf +instance NFData Word where rnf = rwhnf + +instance NFData Integer where rnf = rwhnf + +instance NFData Float where rnf = rwhnf + +instance NFData Double where rnf = rwhnf + +instance NFData Char where rnf = rwhnf + +instance NFData Bool where rnf = rwhnf -instance NFData Char where rnf = rwhnf -instance NFData Bool where rnf = rwhnf instance NFData Ordering where rnf = rwhnf -instance NFData () where rnf = rwhnf -instance NFData Int8 where rnf = rwhnf -instance NFData Int16 where rnf = rwhnf -instance NFData Int32 where rnf = rwhnf -instance NFData Int64 where rnf = rwhnf +instance NFData () where rnf = rwhnf + +instance NFData Int8 where rnf = rwhnf + +instance NFData Int16 where rnf = rwhnf + +instance NFData Int32 where rnf = rwhnf -instance NFData Word8 where rnf = rwhnf -instance NFData Word16 where rnf = rwhnf -instance NFData Word32 where rnf = rwhnf -instance NFData Word64 where rnf = rwhnf +instance NFData Int64 where rnf = rwhnf + +instance NFData Word8 where rnf = rwhnf + +instance NFData Word16 where rnf = rwhnf + +instance NFData Word32 where rnf = rwhnf + +instance NFData Word64 where rnf = rwhnf -- | @since 1.4.4.0 instance NFData MaskingState where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData (Proxy a) where rnf Proxy = () --- |@since 1.4.3.0 -instance NFData1 Proxy where liftRnf _ Proxy = () + +-- | @since 1.4.3.0 +instance NFData1 Proxy where liftRnf _ Proxy = () -- | @since 1.4.3.0 instance NFData (a :~: b) where rnf = rwhnf + -- | @since 1.4.3.0 instance NFData1 ((:~:) a) where liftRnf _ = rwhnf + -- | @since 1.4.3.0 instance NFData2 (:~:) where liftRnf2 _ _ = rwhnf -#if MIN_VERSION_base(4,10,0) -- | @since 1.4.3.0 instance NFData (a :~~: b) where rnf = rwhnf + -- | @since 1.4.3.0 instance NFData1 ((:~~:) a) where liftRnf _ = rwhnf + -- | @since 1.4.3.0 instance NFData2 (:~~:) where liftRnf2 _ _ = rwhnf -#endif --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Identity a) where - rnf = rnf1 + rnf = rnf1 --- |@since 1.4.3.0 +-- | @since 1.4.3.0 instance NFData1 Identity where - liftRnf r = r . runIdentity + liftRnf r = r . runIdentity -- | Defined as @'rnf' = 'absurd'@. -- -- @since 1.4.0.0 instance NFData Void where - rnf = absurd + rnf = absurd --- |@since 1.4.0.0 -instance NFData Natural where rnf = rwhnf +-- | @since 1.4.0.0 +instance NFData Natural where rnf = rwhnf --- |@since 1.3.0.0 +-- | @since 1.3.0.0 instance NFData (Fixed a) where rnf = rwhnf --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Fixed where liftRnf _ = rwhnf --- |This instance is for convenience and consistency with 'seq'. --- This assumes that WHNF is equivalent to NF for functions. +-- | This instance is for convenience and consistency with 'seq'. +-- This assumes that WHNF is equivalent to NF for functions. -- --- @since 1.3.0.0 +-- @since 1.3.0.0 instance NFData (a -> b) where rnf = rwhnf ---Rational and complex numbers. +-- Rational and complex numbers. -- | Available on @base >=4.9@ -- @@ -528,346 +524,368 @@ instance NFData a => NFData (Ratio a) where rnf x = rnf (numerator x, denominator x) instance (NFData a) => NFData (Complex a) where - rnf (x:+y) = rnf x `seq` - rnf y `seq` - () + rnf (x :+ y) = rnf x `seq` rnf y `seq` () instance NFData a => NFData (Maybe a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Maybe where - liftRnf _r Nothing = () - liftRnf r (Just x) = r x + liftRnf _r Nothing = () + liftRnf r (Just x) = r x instance (NFData a, NFData b) => NFData (Either a b) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance (NFData a) => NFData1 (Either a) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData2 Either where - liftRnf2 l _r (Left x) = l x - liftRnf2 _l r (Right y) = r y + liftRnf2 l _r (Left x) = l x + liftRnf2 _l r (Right y) = r y --- |@since 1.3.0.0 +-- | @since 1.3.0.0 instance NFData Data.Version.Version where - rnf (Data.Version.Version branch tags) = rnf branch `seq` rnf tags + rnf (Data.Version.Version branch tags) = rnf branch `seq` rnf tags instance NFData a => NFData [a] where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 [] where - liftRnf r = go - where - go [] = () - go (x:xs) = r x `seq` go xs + liftRnf r = go + where + go [] = () + go (x : xs) = r x `seq` go xs --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (ZipList a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 ZipList where - liftRnf r = liftRnf r . getZipList + liftRnf r = liftRnf r . getZipList --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Const a b) where - rnf = rnf . getConst --- |@since 1.4.3.0 + rnf = rnf . getConst + +-- | @since 1.4.3.0 instance NFData a => NFData1 (Const a) where - liftRnf _ = rnf . getConst --- |@since 1.4.3.0 + liftRnf _ = rnf . getConst + +-- | @since 1.4.3.0 instance NFData2 Const where - liftRnf2 r _ = r . getConst + liftRnf2 r _ = r . getConst -- We should use MIN_VERSION array(0,5,1,1) but that's not possible. -- There isn't an underscore to not break C preprocessor instance (NFData a, NFData b) => NFData (Array a b) where - rnf x = rnf (bounds x, Data.Array.elems x) + rnf x = rnf (bounds x, Data.Array.elems x) --- |@since 1.4.3.0 +-- | @since 1.4.3.0 instance (NFData a) => NFData1 (Array a) where - liftRnf r x = rnf (bounds x) `seq` liftRnf r (Data.Array.elems x) + liftRnf r x = rnf (bounds x) `seq` liftRnf r (Data.Array.elems x) --- |@since 1.4.3.0 +-- | @since 1.4.3.0 instance NFData2 Array where - liftRnf2 r r' x = liftRnf2 r r (bounds x) `seq` liftRnf r' (Data.Array.elems x) + liftRnf2 r r' x = liftRnf2 r r (bounds x) `seq` liftRnf r' (Data.Array.elems x) --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Down a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Down where - liftRnf r (Down x) = r x + liftRnf r (Down x) = r x --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Dual a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Dual where - liftRnf r (Dual x) = r x + liftRnf r (Dual x) = r x --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Mon.First a) where rnf = rnf1 --- |@since 1.4.3.0 -instance NFData1 Mon.First where - liftRnf r (Mon.First x) = liftRnf r x --- |@since 1.4.0.0 +-- | @since 1.4.3.0 +instance NFData1 Mon.First where + liftRnf r (Mon.First x) = liftRnf r x + +-- | @since 1.4.0.0 instance NFData a => NFData (Mon.Last a) where rnf = rnf1 --- |@since 1.4.3.0 -instance NFData1 Mon.Last where - liftRnf r (Mon.Last x) = liftRnf r x --- |@since 1.4.0.0 +-- | @since 1.4.3.0 +instance NFData1 Mon.Last where + liftRnf r (Mon.Last x) = liftRnf r x + +-- | @since 1.4.0.0 instance NFData Any where rnf = rnf . getAny --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData All where rnf = rnf . getAll --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Sum a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Sum where - liftRnf r (Sum x) = r x + liftRnf r (Sum x) = r x --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData a => NFData (Product a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Product where - liftRnf r (Product x) = r x + liftRnf r (Product x) = r x --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData (StableName a) where - rnf = rwhnf -- assumes `data StableName a = StableName (StableName# a)` --- |@since 1.4.3.0 + rnf = rwhnf -- assumes `data StableName a = StableName (StableName# a)` + +-- | @since 1.4.3.0 instance NFData1 StableName where - liftRnf _ = rwhnf + liftRnf _ = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData ThreadId where - rnf = rwhnf -- assumes `data ThreadId = ThreadId ThreadId#` + rnf = rwhnf -- assumes `data ThreadId = ThreadId ThreadId#` --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData Unique where - rnf = rwhnf -- assumes `newtype Unique = Unique Integer` + rnf = rwhnf -- assumes `newtype Unique = Unique Integer` -- | __NOTE__: Prior to @deepseq-1.4.4.0@ this instance was only defined for @base-4.8.0.0@ and later. -- -- @since 1.4.0.0 instance NFData TypeRep where - rnf tyrep = rnfTypeRep tyrep + rnf tyrep = rnfTypeRep tyrep -- | __NOTE__: Prior to @deepseq-1.4.4.0@ this instance was only defined for @base-4.8.0.0@ and later. -- -- @since 1.4.0.0 instance NFData TyCon where - rnf tycon = rnfTyCon tycon + rnf tycon = rnfTyCon tycon -#if MIN_VERSION_base(4,10,0) --- |@since 1.4.8.0 +-- | @since 1.4.8.0 instance NFData (Reflection.TypeRep a) where - rnf tr = Reflection.rnfTypeRep tr + rnf tr = Reflection.rnfTypeRep tr --- |@since 1.4.8.0 +-- | @since 1.4.8.0 instance NFData Reflection.Module where - rnf modul = Reflection.rnfModule modul -#endif + rnf modul = Reflection.rnfModule modul -- | __NOTE__: Only strict in the reference and not the referenced value. -- -- @since 1.4.2.0 instance NFData (IORef a) where - rnf = rwhnf --- |@since 1.4.3.0 + rnf = rwhnf + +-- | @since 1.4.3.0 instance NFData1 IORef where - liftRnf _ = rwhnf + liftRnf _ = rwhnf -- | __NOTE__: Only strict in the reference and not the referenced value. -- -- @since 1.4.2.0 instance NFData (STRef s a) where - rnf = rwhnf --- |@since 1.4.3.0 + rnf = rwhnf + +-- | @since 1.4.3.0 instance NFData1 (STRef s) where - liftRnf _ = rwhnf --- |@since 1.4.3.0 + liftRnf _ = rwhnf + +-- | @since 1.4.3.0 instance NFData2 STRef where - liftRnf2 _ _ = rwhnf + liftRnf2 _ _ = rwhnf -- | __NOTE__: Only strict in the reference and not the referenced value. -- -- @since 1.4.2.0 instance NFData (MVar a) where rnf = rwhnf --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 MVar where - liftRnf _ = rwhnf + liftRnf _ = rwhnf ---------------------------------------------------------------------------- -- GHC Specifics --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData Fingerprint where - rnf (Fingerprint _ _) = () + rnf (Fingerprint _ _) = () ---------------------------------------------------------------------------- -- Foreign.Ptr --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData (Ptr a) where - rnf = rwhnf --- |@since 1.4.3.0 + rnf = rwhnf + +-- | @since 1.4.3.0 instance NFData1 Ptr where - liftRnf _ = rwhnf + liftRnf _ = rwhnf --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData (FunPtr a) where - rnf = rwhnf --- |@since 1.4.3.0 + rnf = rwhnf + +-- | @since 1.4.3.0 instance NFData1 FunPtr where - liftRnf _ = rwhnf + liftRnf _ = rwhnf ---------------------------------------------------------------------------- -- Foreign.C.Types --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CChar where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CSChar where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CUChar where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CShort where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CUShort where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CInt where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CUInt where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CLong where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CULong where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CPtrdiff where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CSize where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CWchar where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CSigAtomic where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CLLong where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CULLong where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CIntPtr where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CUIntPtr where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CIntMax where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CUIntMax where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CClock where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CTime where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CUSeconds where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CSUSeconds where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CFloat where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CDouble where rnf = rwhnf -- NOTE: The types `CFile`, `CFPos`, and `CJmpBuf` below are not -- newtype wrappers rather defined as field-less single-constructor -- types. --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CFile where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CFpos where rnf = rwhnf --- |@since 1.4.0.0 +-- | @since 1.4.0.0 instance NFData CJmpBuf where rnf = rwhnf -#if MIN_VERSION_base(4,10,0) -- | @since 1.4.3.0 instance NFData CBool where rnf = rwhnf -#endif ---------------------------------------------------------------------------- -- System.Exit --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData ExitCode where rnf (ExitFailure n) = rnf n - rnf ExitSuccess = () + rnf ExitSuccess = () ---------------------------------------------------------------------------- -- instances previously provided by semigroups package --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData a => NFData (NonEmpty a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 NonEmpty where liftRnf r (x :| xs) = r x `seq` liftRnf r xs --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData a => NFData (Min a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Min where liftRnf r (Min a) = r a --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData a => NFData (Max a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Max where liftRnf r (Max a) = r a --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance (NFData a, NFData b) => NFData (Arg a b) where rnf = rnf2 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance (NFData a) => NFData1 (Arg a) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData2 Arg where liftRnf2 r r' (Arg a b) = r a `seq` r' b `seq` () --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData a => NFData (Semi.First a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Semi.First where liftRnf r (Semi.First a) = r a --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData a => NFData (Semi.Last a) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 Semi.Last where liftRnf r (Semi.Last a) = r a --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData m => NFData (WrappedMonoid m) where rnf = rnf1 --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData1 WrappedMonoid where liftRnf r (WrapMonoid a) = r a @@ -882,16 +900,16 @@ instance NFData1 Option where ---------------------------------------------------------------------------- -- GHC.Stack --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData SrcLoc where - rnf (SrcLoc a b c d e f g) = rnf a `seq` rnf b `seq` rnf c `seq` - rnf d `seq` rnf e `seq` rnf f `seq` rnf g + rnf (SrcLoc a b c d e f g) = + rnf a `seq` rnf b `seq` rnf c `seq` rnf d `seq` rnf e `seq` rnf f `seq` rnf g --- |@since 1.4.2.0 +-- | @since 1.4.2.0 instance NFData CallStack where rnf EmptyCallStack = () rnf (PushCallStack a b c) = rnf a `seq` rnf b `seq` rnf c - rnf (FreezeCallStack a) = rnf a + rnf (FreezeCallStack a) = rnf a ---------------------------------------------------------------------------- -- Tuples @@ -915,88 +933,167 @@ instance NFData1 Solo where #endif #endif -instance (NFData a, NFData b) => NFData (a,b) where rnf = rnf2 --- |@since 1.4.3.0 +instance (NFData a, NFData b) => NFData (a, b) where rnf = rnf2 + +-- | @since 1.4.3.0 instance (NFData a) => NFData1 ((,) a) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 + +-- | @since 1.4.3.0 instance NFData2 (,) where - liftRnf2 r r' (x,y) = r x `seq` r' y + liftRnf2 r r' (x, y) = r x `seq` r' y -- Code below is generated, see generate-nfdata-tuple.hs -instance (NFData a1, NFData a2, NFData a3) => - NFData (a1, a2, a3) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2) => - NFData1 ((,,) a1 a2) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1) => - NFData2 ((,,) a1) where - liftRnf2 r r' (x1,x2,x3) = rnf x1 `seq` r x2 `seq` r' x3 +instance + (NFData a1, NFData a2, NFData a3) => + NFData (a1, a2, a3) + where + rnf = rnf2 -instance (NFData a1, NFData a2, NFData a3, NFData a4) => - NFData (a1, a2, a3, a4) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3) => - NFData1 ((,,,) a1 a2 a3) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1, NFData a2) => - NFData2 ((,,,) a1 a2) where - liftRnf2 r r' (x1,x2,x3,x4) = rnf x1 `seq` rnf x2 `seq` r x3 `seq` r' x4 +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2) => + NFData1 ((,,) a1 a2) + where + liftRnf = liftRnf2 rnf -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => - NFData (a1, a2, a3, a4, a5) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4) => - NFData1 ((,,,,) a1 a2 a3 a4) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3) => - NFData2 ((,,,,) a1 a2 a3) where - liftRnf2 r r' (x1,x2,x3,x4,x5) = rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` r x4 `seq` r' x5 +-- | @since 1.4.3.0 +instance + (NFData a1) => + NFData2 ((,,) a1) + where + liftRnf2 r r' (x1, x2, x3) = + rnf x1 `seq` r x2 `seq` r' x3 + +instance + (NFData a1, NFData a2, NFData a3, NFData a4) => + NFData (a1, a2, a3, a4) + where + rnf = rnf2 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => - NFData (a1, a2, a3, a4, a5, a6) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => - NFData1 ((,,,,,) a1 a2 a3 a4 a5) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4) => - NFData2 ((,,,,,) a1 a2 a3 a4) where - liftRnf2 r r' (x1,x2,x3,x4,x5,x6) = rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` r x5 `seq` r' x6 +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3) => + NFData1 ((,,,) a1 a2 a3) + where + liftRnf = liftRnf2 rnf -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => - NFData (a1, a2, a3, a4, a5, a6, a7) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => - NFData1 ((,,,,,,) a1 a2 a3 a4 a5 a6) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => - NFData2 ((,,,,,,) a1 a2 a3 a4 a5) where - liftRnf2 r r' (x1,x2,x3,x4,x5,x6,x7) = rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` rnf x5 `seq` r x6 `seq` r' x7 +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2) => + NFData2 ((,,,) a1 a2) + where + liftRnf2 r r' (x1, x2, x3, x4) = + rnf x1 `seq` rnf x2 `seq` r x3 `seq` r' x4 + +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => + NFData (a1, a2, a3, a4, a5) + where + rnf = rnf2 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => - NFData (a1, a2, a3, a4, a5, a6, a7, a8) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => - NFData1 ((,,,,,,,) a1 a2 a3 a4 a5 a6 a7) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => - NFData2 ((,,,,,,,) a1 a2 a3 a4 a5 a6) where - liftRnf2 r r' (x1,x2,x3,x4,x5,x6,x7,x8) = rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` rnf x5 `seq` rnf x6 `seq` r x7 `seq` r' x8 +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4) => + NFData1 ((,,,,) a1 a2 a3 a4) + where + liftRnf = liftRnf2 rnf -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => - NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) where rnf = rnf2 --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => - NFData1 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7 a8) where liftRnf = liftRnf2 rnf --- |@since 1.4.3.0 -instance (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => - NFData2 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7) where - liftRnf2 r r' (x1,x2,x3,x4,x5,x6,x7,x8,x9) = rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` rnf x5 `seq` rnf x6 `seq` rnf x7 `seq` r x8 `seq` r' x9 +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3) => + NFData2 ((,,,,) a1 a2 a3) + where + liftRnf2 r r' (x1, x2, x3, x4, x5) = + rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` r x4 `seq` r' x5 + +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => + NFData (a1, a2, a3, a4, a5, a6) + where + rnf = rnf2 + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => + NFData1 ((,,,,,) a1 a2 a3 a4 a5) + where + liftRnf = liftRnf2 rnf + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4) => + NFData2 ((,,,,,) a1 a2 a3 a4) + where + liftRnf2 r r' (x1, x2, x3, x4, x5, x6) = + rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` r x5 `seq` r' x6 + +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => + NFData (a1, a2, a3, a4, a5, a6, a7) + where + rnf = rnf2 + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => + NFData1 ((,,,,,,) a1 a2 a3 a4 a5 a6) + where + liftRnf = liftRnf2 rnf + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => + NFData2 ((,,,,,,) a1 a2 a3 a4 a5) + where + liftRnf2 r r' (x1, x2, x3, x4, x5, x6, x7) = + rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` rnf x5 `seq` r x6 `seq` r' x7 + +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => + NFData (a1, a2, a3, a4, a5, a6, a7, a8) + where + rnf = rnf2 + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => + NFData1 ((,,,,,,,) a1 a2 a3 a4 a5 a6 a7) + where + liftRnf = liftRnf2 rnf + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => + NFData2 ((,,,,,,,) a1 a2 a3 a4 a5 a6) + where + liftRnf2 r r' (x1, x2, x3, x4, x5, x6, x7, x8) = + rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` rnf x5 `seq` rnf x6 `seq` r x7 `seq` r' x8 + +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => + NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) + where + rnf = rnf2 + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => + NFData1 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7 a8) + where + liftRnf = liftRnf2 rnf + +-- | @since 1.4.3.0 +instance + (NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => + NFData2 ((,,,,,,,,) a1 a2 a3 a4 a5 a6 a7) + where + liftRnf2 r r' (x1, x2, x3, x4, x5, x6, x7, x8, x9) = + rnf x1 `seq` rnf x2 `seq` rnf x3 `seq` rnf x4 `seq` rnf x5 `seq` rnf x6 `seq` rnf x7 `seq` r x8 `seq` r' x9 ---------------------------------------------------------------------------- -- ByteArray -#if BYTEARRAY_IN_BASE +#if MIN_VERSION_base(4,17,0) -- |@since 1.4.7.0 instance NFData ByteArray where rnf (ByteArray _) = () diff --git a/Control/DeepSeq/BackDoor.hs b/Control/DeepSeq/BackDoor.hs deleted file mode 100644 index 343ec56..0000000 --- a/Control/DeepSeq/BackDoor.hs +++ /dev/null @@ -1,33 +0,0 @@ -{-# LANGUAGE CPP #-} - --- | Hack to keep Control.DeepSeq SAFE-inferred --- --- This module only re-export reasonably safe entities from non-safe --- modules when there is no safe alternative - -#if MIN_VERSION_base(4,9,0) || (MIN_VERSION_base(4,6,0) && !MIN_VERSION_base(4,7,0)) -{-# LANGUAGE Safe #-} - -module Control.DeepSeq.BackDoor - {-# WARNING "This module is empty! Do not import me!" #-} - () where - -#else -{-# LANGUAGE Trustworthy #-} - -module Control.DeepSeq.BackDoor - ( module X - ) where - -#if !(MIN_VERSION_base(4,6,0)) --- not SAFE -import GHC.Exts as X ( Down(Down) ) -#endif - -#if MIN_VERSION_base(4,10,0) --- Data.Type.Equality SAFE starting with base-4.10 -#elif MIN_VERSION_base(4,7,0) -import Data.Type.Equality as X ( (:~:) ) -#endif - -#endif diff --git a/changelog.md b/changelog.md index f0921d0..9ced552 100644 --- a/changelog.md +++ b/changelog.md @@ -4,6 +4,8 @@ * Add quantified superclasses to NFData(1,2) ([#88](https://github.com/haskell/deepseq/issues/88)) + * Drop support for GHC < 8.6 + ([#94](https://github.com/haskell/deepseq/pull/94)) ## 1.4.8.1 diff --git a/deepseq.cabal b/deepseq.cabal index 68d5fdb..8b34d75 100644 --- a/deepseq.cabal +++ b/deepseq.cabal @@ -1,6 +1,6 @@ cabal-version: 1.12 name: deepseq -version: 1.4.9.0 +version: 1.5.0.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 @@ -30,10 +30,8 @@ tested-with: GHC==9.2.5, GHC==9.0.2, GHC==8.10.7, - GHC==8.6.5, - GHC==8.4.4, - GHC==8.2.2, - GHC==8.0.2 + GHC==8.8.4, + GHC==8.6.5 extra-source-files: changelog.md @@ -60,12 +58,11 @@ library if impl(ghc >=9.0) build-depends: ghc-prim - build-depends: base >= 4.9 && < 4.19, + build-depends: base >= 4.12 && < 4.19, array >= 0.4 && < 0.6 ghc-options: -Wall exposed-modules: Control.DeepSeq - other-modules: Control.DeepSeq.BackDoor test-suite test Default-Language: Haskell2010 diff --git a/tests/Main.hs b/tests/Main.hs index df78191..4864abb 100644 --- a/tests/Main.hs +++ b/tests/Main.hs @@ -1,6 +1,4 @@ -- Code reused from http://hackage.haskell.org/package/deepseq-generics - -{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE TupleSections #-} @@ -8,6 +6,8 @@ module Main (main) where import Control.Concurrent.MVar +-- IUT +import Control.DeepSeq import Control.Exception import Control.Monad import Data.Bits @@ -18,19 +18,6 @@ import GHC.Generics import System.Exit (exitFailure) import System.IO.Unsafe (unsafePerformIO) --- IUT -import Control.DeepSeq - --- needed for GHC-7.4 compatibility -#if !MIN_VERSION_base(4,6,0) -atomicModifyIORef' :: IORef a -> (a -> (a,b)) -> IO b -atomicModifyIORef' ref f = do - b <- atomicModifyIORef ref - (\x -> let (a, b) = f x - in (a, a `seq` b)) - b `seq` return b -#endif - ---------------------------------------------------------------------------- -- simple hacky abstraction for testing forced evaluation via `rnf`-like functions @@ -40,16 +27,17 @@ seqStateLock = unsafePerformIO $ newMVar () withSeqState :: Word64 -> IO () -> IO () withSeqState expectedState act = withMVar seqStateLock $ \() -> do - 0 <- resetSeqState - () <- act - st <- resetSeqState - unless (st == expectedState) $ do - putStrLn $ "withSeqState: actual seq-state (" ++ - show st ++ - ") doesn't match expected value (" ++ - show expectedState ++ - ")" - exitFailure + 0 <- resetSeqState + () <- act + st <- resetSeqState + unless (st == expectedState) $ do + putStrLn $ + "withSeqState: actual seq-state (" + ++ show st + ++ ") doesn't match expected value (" + ++ show expectedState + ++ ")" + exitFailure seqState :: IORef Word64 seqState = unsafePerformIO $ newIORef 0 @@ -58,24 +46,26 @@ seqState = unsafePerformIO $ newIORef 0 resetSeqState :: IO Word64 resetSeqState = atomicModifyIORef' seqState (0,) --- |Set flag and raise exception is flag already set +-- | Set flag and raise exception is flag already set setSeqState :: Int -> IO () -setSeqState i | 0 <= i && i < 64 = atomicModifyIORef' seqState go - | otherwise = error "seqSeqState: flag index must be in [0..63]" - where - go x | testBit x i = error ("setSeqState: flag #"++show i++" already set") - | otherwise = (setBit x i, ()) +setSeqState i + | 0 <= i && i < 64 = atomicModifyIORef' seqState go + | otherwise = error "seqSeqState: flag index must be in [0..63]" + where + go x + | testBit x i = error ("setSeqState: flag #" ++ show i ++ " already set") + | otherwise = (setBit x i, ()) -- weird type whose NFData instance calls 'setSeqState' when rnf-ed data SeqSet = SeqSet !Int | SeqIgnore - deriving Show + deriving (Show) instance NFData SeqSet where - rnf (SeqSet i) = unsafePerformIO $ setSeqState i - rnf (SeqIgnore) = () - {-# NOINLINE rnf #-} + rnf (SeqSet i) = unsafePerformIO $ setSeqState i + rnf (SeqIgnore) = () + {-# NOINLINE rnf #-} --- |Exception to be thrown for testing 'seq'/'rnf' +-- | Exception to be thrown for testing 'seq'/'rnf' data RnfEx = RnfEx deriving (Eq, Show, Typeable) instance Exception RnfEx @@ -84,108 +74,112 @@ instance NFData RnfEx where rnf e = throw e assertRnfEx :: () -> IO () assertRnfEx v = handleJust isWanted (const $ return ()) $ do - () <- evaluate v - putStrLn "failed to trigger expected RnfEx exception" - exitFailure - where isWanted = guard . (== RnfEx) + () <- evaluate v + putStrLn "failed to trigger expected RnfEx exception" + exitFailure + where + isWanted = guard . (== RnfEx) ---------------------------------------------------------------------------- testCase :: String -> IO a -> IO a testCase testName io = do - putStrLn testName - io + putStrLn testName + io case_1, case_2, case_3 :: IO () case_4_1, case_4_2, case_4_3, case_4_4 :: IO () -#if __GLASGOW_HASKELL__ >= 706 case_4_1b, case_4_2b, case_4_3b, case_4_4b :: IO () -#endif newtype Case1 = Case1 Int - deriving (Generic) + deriving (Generic) instance NFData Case1 case_1 = testCase "Case1" $ do - assertRnfEx $ rnf $ (Case1 (throw RnfEx)) + assertRnfEx $ rnf $ (Case1 (throw RnfEx)) ---- data Case2 = Case2 Int - deriving (Generic) + deriving (Generic) instance NFData Case2 case_2 = testCase "Case2" $ do - assertRnfEx $ rnf $ (Case2 (throw RnfEx)) + assertRnfEx $ rnf $ (Case2 (throw RnfEx)) ---- data Case3 = Case3 RnfEx - deriving (Generic) + deriving (Generic) instance NFData Case3 case_3 = testCase "Case3" $ do - assertRnfEx $ rnf $ Case3 RnfEx + assertRnfEx $ rnf $ Case3 RnfEx ---- -data Case4 a = Case4a - | Case4b a a - | Case4c a (Case4 a) - deriving ( Generic -#if __GLASGOW_HASKELL__ >= 706 - , Generic1 -#endif - ) +data Case4 a + = Case4a + | Case4b a a + | Case4c a (Case4 a) + deriving + ( Generic + , Generic1 + ) instance NFData a => NFData (Case4 a) -#if __GLASGOW_HASKELL__ >= 706 instance NFData1 Case4 -#endif case_4_1 = testCase "Case4.1" $ withSeqState 0x0 $ do - evaluate $ rnf $ (Case4a :: Case4 SeqSet) + evaluate $ rnf $ (Case4a :: Case4 SeqSet) case_4_2 = testCase "Case4.2" $ withSeqState 0x3 $ do - evaluate $ rnf $ (Case4b (SeqSet 0) (SeqSet 1) :: Case4 SeqSet) + evaluate $ rnf $ (Case4b (SeqSet 0) (SeqSet 1) :: Case4 SeqSet) case_4_3 = testCase "Case4.3" $ withSeqState (bit 55) $ do - evaluate $ rnf $ (Case4b SeqIgnore (SeqSet 55) :: Case4 SeqSet) + evaluate $ rnf $ (Case4b SeqIgnore (SeqSet 55) :: Case4 SeqSet) case_4_4 = testCase "Case4.4" $ withSeqState 0xffffffffffffffff $ do - evaluate $ rnf $ (genCase 63) - where - genCase n | n > 1 = Case4c (SeqSet n) (genCase (n-1)) - | otherwise = Case4b (SeqSet 0) (SeqSet 1) + evaluate $ rnf $ (genCase 63) + where + genCase n + | n > 1 = Case4c (SeqSet n) (genCase (n - 1)) + | otherwise = Case4b (SeqSet 0) (SeqSet 1) -#if __GLASGOW_HASKELL__ >= 706 case_4_1b = testCase "Case4.1b" $ withSeqState 0x0 $ do - evaluate $ rnf1 $ (Case4a :: Case4 SeqSet) + evaluate $ rnf1 $ (Case4a :: Case4 SeqSet) case_4_2b = testCase "Case4.2b" $ withSeqState 0x3 $ do - evaluate $ rnf1 $ (Case4b (SeqSet 0) (SeqSet 1) :: Case4 SeqSet) + evaluate $ rnf1 $ (Case4b (SeqSet 0) (SeqSet 1) :: Case4 SeqSet) case_4_3b = testCase "Case4.3b" $ withSeqState (bit 55) $ do - evaluate $ rnf1 $ (Case4b SeqIgnore (SeqSet 55) :: Case4 SeqSet) + evaluate $ rnf1 $ (Case4b SeqIgnore (SeqSet 55) :: Case4 SeqSet) case_4_4b = testCase "Case4.4b" $ withSeqState 0xffffffffffffffff $ do - evaluate $ rnf1 $ (genCase 63) - where - genCase n | n > 1 = Case4c (SeqSet n) (genCase (n-1)) - | otherwise = Case4b (SeqSet 0) (SeqSet 1) -#endif + evaluate $ rnf1 $ (genCase 63) + where + genCase n + | n > 1 = Case4c (SeqSet n) (genCase (n - 1)) + | otherwise = Case4b (SeqSet 0) (SeqSet 1) ---------------------------------------------------------------------------- main :: IO () -main = sequence_ - [ case_1, case_2, case_3 - , case_4_1, case_4_2, case_4_3, case_4_4 -#if __GLASGOW_HASKELL__ >= 706 - , case_4_1b, case_4_2b, case_4_3b, case_4_4b -#endif - ] +main = + sequence_ + [ case_1 + , case_2 + , case_3 + , case_4_1 + , case_4_2 + , case_4_3 + , case_4_4 + , case_4_1b + , case_4_2b + , case_4_3b + , case_4_4b + ]