Skip to content

Commit

Permalink
Merge pull request #107 from meooow25/drop-array
Browse files Browse the repository at this point in the history
Drop the dependency on array
  • Loading branch information
mixphix authored Sep 8, 2024
2 parents c104438 + c2432c2 commit c4b5c0d
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 8 deletions.
12 changes: 7 additions & 5 deletions Control/DeepSeq.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

Expand Down Expand Up @@ -94,7 +94,6 @@ module Control.DeepSeq (
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
Expand All @@ -118,6 +117,8 @@ import Data.Void (Void, absurd)
import Data.Word
import Foreign.C.Types
import Foreign.Ptr
import GHC.Arr (Array)
import qualified GHC.Arr
import GHC.Fingerprint.Type (Fingerprint (..))
import GHC.Generics
import GHC.Stack.Types (CallStack (..), SrcLoc (..))
Expand Down Expand Up @@ -628,15 +629,16 @@ instance NFData2 Const where
-- 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 (GHC.Arr.bounds x, GHC.Arr.elems x)

-- | @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 (GHC.Arr.bounds x) `seq` liftRnf r (GHC.Arr.elems x)

-- | @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 (GHC.Arr.bounds x) `seq` liftRnf r' (GHC.Arr.elems x)

-- | @since 1.4.0.0
instance NFData a => NFData (Down a) where rnf = rnf1
Expand Down
4 changes: 1 addition & 3 deletions deepseq.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -61,8 +61,7 @@ library
if impl(ghc >=9.0)
build-depends: ghc-prim

build-depends: base >= 4.12 && < 4.21,
array >= 0.4 && < 0.6
build-depends: base >= 4.12 && < 4.21
ghc-options: -Wall

exposed-modules: Control.DeepSeq
Expand All @@ -73,7 +72,6 @@ test-suite test
main-is: Main.hs
type: exitcode-stdio-1.0
build-depends:
array,
base,
deepseq,
ghc-prim
Expand Down

0 comments on commit c4b5c0d

Please sign in to comment.