66{-# LANGUAGE MultiParamTypeClasses #-}
77{-# LANGUAGE PolyKinds #-}
88{-# LANGUAGE QuantifiedConstraints #-}
9- {-# LANGUAGE Safe #-}
9+ {-# LANGUAGE Trustworthy #-}
1010{-# LANGUAGE TypeFamilies #-}
1111{-# LANGUAGE TypeOperators #-}
1212
@@ -94,7 +94,6 @@ module Control.DeepSeq (
9494import Control.Applicative
9595import Control.Concurrent (MVar , ThreadId )
9696import Control.Exception (MaskingState (.. ))
97- import Data.Array
9897import Data.Complex
9998import Data.Fixed
10099import Data.Functor.Compose
@@ -118,6 +117,8 @@ import Data.Void (Void, absurd)
118117import Data.Word
119118import Foreign.C.Types
120119import Foreign.Ptr
120+ import GHC.Arr (Array )
121+ import qualified GHC.Arr
121122import GHC.Fingerprint.Type (Fingerprint (.. ))
122123import GHC.Generics
123124import GHC.Stack.Types (CallStack (.. ), SrcLoc (.. ))
@@ -628,15 +629,16 @@ instance NFData2 Const where
628629-- We should use MIN_VERSION array(0,5,1,1) but that's not possible.
629630-- There isn't an underscore to not break C preprocessor
630631instance (NFData a , NFData b ) => NFData (Array a b ) where
631- rnf x = rnf (bounds x, Data.Array . elems x)
632+ rnf x = rnf (GHC.Arr. bounds x, GHC.Arr . elems x)
632633
633634-- | @since 1.4.3.0
634635instance (NFData a ) => NFData1 (Array a ) where
635- liftRnf r x = rnf (bounds x) `seq` liftRnf r (Data.Array . elems x)
636+ liftRnf r x = rnf (GHC.Arr. bounds x) `seq` liftRnf r (GHC.Arr . elems x)
636637
637638-- | @since 1.4.3.0
638639instance NFData2 Array where
639- liftRnf2 r r' x = liftRnf2 r r (bounds x) `seq` liftRnf r' (Data.Array. elems x)
640+ liftRnf2 r r' x =
641+ liftRnf2 r r (GHC.Arr. bounds x) `seq` liftRnf r' (GHC.Arr. elems x)
640642
641643-- | @since 1.4.0.0
642644instance NFData a => NFData (Down a ) where rnf = rnf1
0 commit comments