Skip to content
Snippets Groups Projects
Commit 4077e344 authored by Ryan Scott's avatar Ryan Scott
Browse files

Adapt to `unsafeCoerce#` no longer being exported from `GHC.{Base,Prim}`

Commit ghc@74ad75e8
moved `unsafeCoerce#` from `GHC.Prim` to `Unsafe.Coerce`, making it
no longer possible to import `unsafeCoerce#` from `GHC.Prim` (or
`GHC.Base`, which reexported it). Sadly, a large number of Hackage
libraries obtain `unsafeCoerce#` by importing these modules instead
of `GHC.Exts`. As a result, all of these libraries need to be patched
to import `unsafeCoerce#` from somewhere else instead.
parent 225efbce
No related branches found
No related tags found
1 merge request!75Adapt to `unsafeCoerce#` no longer being exported from `GHC.{Base,Prim}`
......@@ -720,9 +720,18 @@ index ed593dc..197f5b8 100644
| otherwise = return (lhead s')
where s' = drop i s
diff --git a/src/Data/Edison/Seq/FingerSeq.hs b/src/Data/Edison/Seq/FingerSeq.hs
index c74c70b..b069665 100644
index c74c70b..8ecb4ee 100644
--- a/src/Data/Edison/Seq/FingerSeq.hs
+++ b/src/Data/Edison/Seq/FingerSeq.hs
@@ -46,7 +46,7 @@ import Data.Semigroup as SG
import Test.QuickCheck
#ifdef __GLASGOW_HASKELL__
-import GHC.Base (unsafeCoerce#)
+import GHC.Exts (unsafeCoerce#)
#endif
@@ -243,7 +243,7 @@ lookupM i (Seq xs)
case FT.splitTree (> (SizeM i)) (SizeM 0) xs of
FT.Split _ (Elem x) _ -> return x
......
diff --git a/Data/Atomics.hs b/Data/Atomics.hs
index 2ed2947..d9d0946 100644
--- a/Data/Atomics.hs
+++ b/Data/Atomics.hs
@@ -54,10 +54,10 @@ import Data.IORef
import GHC.IORef hiding (atomicModifyIORef)
import GHC.STRef
#if MIN_VERSION_base(4,7,0)
-import GHC.Prim hiding ((==#))
+import GHC.Exts hiding ((==#))
import qualified GHC.PrimopWrappers as GPW
#else
-import GHC.Prim
+import GHC.Exts
#endif
import GHC.Base (Int(I#))
import GHC.IO (IO(IO))
diff --git a/Data/Atomics/Internal.hs b/Data/Atomics/Internal.hs
index 7b3a119..c3699f4 100644
--- a/Data/Atomics/Internal.hs
+++ b/Data/Atomics/Internal.hs
@@ -16,7 +16,7 @@ module Data.Atomics.Internal
where
import GHC.Base (Int(I#), Any)
-import GHC.Prim (RealWorld, Int#, State#, MutableArray#, MutVar#,
+import GHC.Exts (RealWorld, Int#, State#, MutableArray#, MutVar#,
unsafeCoerce#, reallyUnsafePtrEquality#)
#if MIN_VERSION_base(4,7,0)
diff --git a/Data/Attoparsec/Text/Buffer.hs b/Data/Attoparsec/Text/Buffer.hs
index 9b2f65c..47e72c3 100644
--- a/Data/Attoparsec/Text/Buffer.hs
+++ b/Data/Attoparsec/Text/Buffer.hs
@@ -48,7 +48,7 @@ import Data.Text.Internal.Encoding.Utf16 (chr2)
import Data.Text.Internal.Unsafe.Char (unsafeChr)
import Data.Text.Unsafe (Iter(..))
import Foreign.Storable (sizeOf)
-import GHC.Base (Int(..), indexIntArray#, unsafeCoerce#, writeIntArray#)
+import GHC.Exts (Int(..), indexIntArray#, unsafeCoerce#, writeIntArray#)
import GHC.ST (ST(..), runST)
import Prelude hiding (length)
import qualified Data.Text.Array as A
diff --git a/Basement/Block/Base.hs b/Basement/Block/Base.hs
index 2780529..77d1978 100644
--- a/Basement/Block/Base.hs
+++ b/Basement/Block/Base.hs
@@ -36,7 +36,7 @@ module Basement.Block.Base
, unsafeRecast
) where
-import GHC.Prim
+import GHC.Exts
import GHC.Types
import GHC.ST
import GHC.IO
diff --git a/Basement/BoxedArray.hs b/Basement/BoxedArray.hs
index e73a0c4..a4fa1c5 100644
--- a/Basement/BoxedArray.hs
+++ b/Basement/BoxedArray.hs
@@ -74,7 +74,7 @@ module Basement.BoxedArray
, builderBuild_
) where
-import GHC.Prim
+import GHC.Exts
import GHC.Types
import GHC.ST
import Data.Proxy
diff --git a/Basement/Monad.hs b/Basement/Monad.hs
index 6433f60..806819d 100644
--- a/Basement/Monad.hs
+++ b/Basement/Monad.hs
@@ -33,7 +33,7 @@ import GHC.ST
import GHC.STRef
import GHC.IORef
import GHC.IO
-import GHC.Prim
+import GHC.Exts
import Basement.Compat.Base (Exception, (.), ($), Applicative, Monad)
-- | Primitive monad that can handle mutation.
diff --git a/Data/Concurrent/Deque/ChaseLev.hs b/Data/Concurrent/Deque/ChaseLev.hs
index 5a21a5b..071f4b7 100644
--- a/Data/Concurrent/Deque/ChaseLev.hs
+++ b/Data/Concurrent/Deque/ChaseLev.hs
@@ -40,7 +40,7 @@ import System.IO.Unsafe (unsafePerformIO)
import Text.Printf (printf)
import System.Mem.StableName (makeStableName, hashStableName)
import GHC.Exts (Int(I#))
-import GHC.Prim (reallyUnsafePtrEquality#, unsafeCoerce#)
+import GHC.Exts (reallyUnsafePtrEquality#, unsafeCoerce#)
--------------------------------------------------------------------------------
-- Instances
diff --git a/Data/Concurrent/Deque/ChaseLevUnboxed.hs b/Data/Concurrent/Deque/ChaseLevUnboxed.hs
index 2817f7a..ef268a0 100644
--- a/Data/Concurrent/Deque/ChaseLevUnboxed.hs
+++ b/Data/Concurrent/Deque/ChaseLevUnboxed.hs
@@ -42,7 +42,7 @@ import System.IO.Unsafe (unsafePerformIO)
import Text.Printf (printf)
import System.Mem.StableName (makeStableName, hashStableName)
import GHC.Exts (Int(I#))
-import GHC.Prim (reallyUnsafePtrEquality#, unsafeCoerce#)
+import GHC.Exts (reallyUnsafePtrEquality#, unsafeCoerce#)
--------------------------------------------------------------------------------
-- Instances
diff --git a/Text/Parsers/Frisby.hs b/Text/Parsers/Frisby.hs
index b121472..b4b10bb 100644
--- a/Text/Parsers/Frisby.hs
+++ b/Text/Parsers/Frisby.hs
@@ -192,7 +192,7 @@ import qualified Control.Monad.Fail as Fail
import Prelude hiding((<>))
--inline usable part of Unsafe.Coerce until that module is commonly available
-import GHC.Base (unsafeCoerce#)
+import GHC.Exts (unsafeCoerce#)
unsafeCoerce :: a -> b
unsafeCoerce = unsafeCoerce#
diff --git a/Data/ByteArray/Bytes.hs b/Data/ByteArray/Bytes.hs
index 588247e..16592ec 100644
--- a/Data/ByteArray/Bytes.hs
+++ b/Data/ByteArray/Bytes.hs
@@ -17,7 +17,7 @@ module Data.ByteArray.Bytes
) where
import GHC.Types
-import GHC.Prim
+import GHC.Exts hiding (IsList(..))
import GHC.Ptr
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup
diff --git a/Data/ByteArray/ScrubbedBytes.hs b/Data/ByteArray/ScrubbedBytes.hs
index fa219e5..0291b22 100644
--- a/Data/ByteArray/ScrubbedBytes.hs
+++ b/Data/ByteArray/ScrubbedBytes.hs
@@ -15,7 +15,7 @@ module Data.ByteArray.ScrubbedBytes
) where
import GHC.Types
-import GHC.Prim
+import GHC.Exts hiding (IsList(..))
import GHC.Ptr
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup
diff --git a/Control/Monad/Primitive.hs b/Control/Monad/Primitive.hs
index f182c18..f908b02 100644
--- a/Control/Monad/Primitive.hs
+++ b/Control/Monad/Primitive.hs
@@ -24,7 +24,7 @@ module Control.Monad.Primitive (
) where
import GHC.Prim ( State#, RealWorld, touch# )
-import GHC.Base ( unsafeCoerce#, realWorld# )
+import GHC.Exts ( unsafeCoerce#, realWorld# )
#if MIN_VERSION_base(4,4,0)
import GHC.Base ( seq# )
#else
diff --git a/Data/Primitive/Array.hs b/Data/Primitive/Array.hs
index 13352f6..d363a97 100644
--- a/Data/Primitive/Array.hs
......@@ -22,6 +35,19 @@ index 13352f6..d363a97 100644
fail _ = empty
instance MonadPlus Array where
diff --git a/Data/Primitive/ByteArray.hs b/Data/Primitive/ByteArray.hs
index 5272053..b555df7 100644
--- a/Data/Primitive/ByteArray.hs
+++ b/Data/Primitive/ByteArray.hs
@@ -61,7 +61,7 @@ import GHC.Base ( Int(..) )
#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts ( IsList(..) )
#endif
-import GHC.Prim
+import GHC.Exts
#if __GLASGOW_HASKELL__ >= 706
hiding (setByteArray#)
#endif
diff --git a/Data/Primitive/MutVar.hs b/Data/Primitive/MutVar.hs
index f707bfb..04993fa 100644
--- a/Data/Primitive/MutVar.hs
......@@ -40,6 +66,19 @@ index f707bfb..04993fa 100644
case readMutVar# mv# s# of
(# s'#, a #) -> let a' = g a in a' `seq` writeMutVar# mv# a' s'#
-
diff --git a/Data/Primitive/PrimArray.hs b/Data/Primitive/PrimArray.hs
index 33d81c2..902044b 100644
--- a/Data/Primitive/PrimArray.hs
+++ b/Data/Primitive/PrimArray.hs
@@ -94,7 +94,7 @@ module Data.Primitive.PrimArray
, mapMaybePrimArrayP
) where
-import GHC.Prim
+import GHC.Exts
import GHC.Base ( Int(..) )
import GHC.Exts (build)
import GHC.Ptr
diff --git a/Data/Primitive/SmallArray.hs b/Data/Primitive/SmallArray.hs
index 3a50cf2..7e0eb41 100644
--- a/Data/Primitive/SmallArray.hs
......@@ -64,6 +103,32 @@ index 3a50cf2..7e0eb41 100644
fail _ = emptySmallArray
instance MonadPlus SmallArray where
diff --git a/Data/Primitive/Types.hs b/Data/Primitive/Types.hs
index fd36ea0..0269996 100644
--- a/Data/Primitive/Types.hs
+++ b/Data/Primitive/Types.hs
@@ -49,7 +49,7 @@ import GHC.Ptr (
Ptr(..), FunPtr(..)
)
-import GHC.Prim
+import GHC.Exts
#if __GLASGOW_HASKELL__ >= 706
hiding (setByteArray#)
#endif
diff --git a/Data/Primitive/UnliftedArray.hs b/Data/Primitive/UnliftedArray.hs
index 75a4847..34be7d4 100644
--- a/Data/Primitive/UnliftedArray.hs
+++ b/Data/Primitive/UnliftedArray.hs
@@ -85,7 +85,7 @@ module Data.Primitive.UnliftedArray
import Data.Typeable
import Control.Applicative
-import GHC.Prim
+import GHC.Exts
import GHC.Base (Int(..),build)
import Control.Monad.Primitive
diff --git a/primitive.cabal b/primitive.cabal
index 8cd2fe2..fbf74be 100644
--- a/primitive.cabal
......
diff --git a/Control/Monad/Primitive.hs b/Control/Monad/Primitive.hs
index 2e7324d..cabec3d 100644
--- a/Control/Monad/Primitive.hs
+++ b/Control/Monad/Primitive.hs
@@ -24,7 +24,7 @@ module Control.Monad.Primitive (
) where
import GHC.Exts ( State#, RealWorld, noDuplicate#, touch# )
-import GHC.Base ( unsafeCoerce#, realWorld# )
+import GHC.Exts ( unsafeCoerce#, realWorld# )
#if MIN_VERSION_base(4,4,0)
import GHC.Base ( seq# )
#else
......@@ -22,3 +22,29 @@ index 5bb9323..3df3a9c 100644
make = makeRegexM
q <- make r
matchM q x
diff --git a/Text/Regex/TDFA/NewDFA/Engine.hs b/Text/Regex/TDFA/NewDFA/Engine.hs
index eaf6be1..8af0f2c 100644
--- a/Text/Regex/TDFA/NewDFA/Engine.hs
+++ b/Text/Regex/TDFA/NewDFA/Engine.hs
@@ -10,7 +10,7 @@ import Data.Array.Base(unsafeRead,unsafeWrite,STUArray(..))
-- #ifdef __GLASGOW_HASKELL__
import GHC.Arr(STArray(..))
import GHC.ST(ST(..))
-import GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
+import GHC.Exts(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
{-
-- #else
import Control.Monad.ST(ST)
diff --git a/Text/Regex/TDFA/NewDFA/Engine_FA.hs b/Text/Regex/TDFA/NewDFA/Engine_FA.hs
index e0f45b4..39d0f40 100644
--- a/Text/Regex/TDFA/NewDFA/Engine_FA.hs
+++ b/Text/Regex/TDFA/NewDFA/Engine_FA.hs
@@ -10,7 +10,7 @@ import Data.Array.Base(unsafeRead,unsafeWrite,STUArray(..))
-- #ifdef __GLASGOW_HASKELL__
import GHC.Arr(STArray(..))
import GHC.ST(ST(..))
-import GHC.Prim(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
+import GHC.Exts(MutableByteArray#,RealWorld,Int#,sizeofMutableByteArray#,unsafeCoerce#)
{-
-- #else
import Control.Monad.ST(ST)
diff --git a/src/Data/Store/Core.hs b/src/Data/Store/Core.hs
index d6699a7..05c0949 100644
--- a/src/Data/Store/Core.hs
+++ b/src/Data/Store/Core.hs
@@ -49,7 +49,7 @@ import Data.Word
import Foreign.ForeignPtr (ForeignPtr, withForeignPtr, castForeignPtr)
import Foreign.Ptr
import Foreign.Storable as Storable
-import GHC.Prim (unsafeCoerce#, RealWorld, ByteArray#, copyByteArrayToAddr#, copyAddrToByteArray#)
+import GHC.Exts (unsafeCoerce#, RealWorld, ByteArray#, copyByteArrayToAddr#, copyAddrToByteArray#)
import GHC.Ptr (Ptr(..))
import GHC.Types (IO(..), Int(..))
import Prelude
......@@ -52,7 +52,7 @@ index b813e47..f359ef1 100644
=> proxy c -> (forall a. c a => f a) -> Rec f ts
rpureConstrained _ f = go (rpure Proxy)
diff --git a/Data/Vinyl/SRec.hs b/Data/Vinyl/SRec.hs
index 6f850c8..68c6893 100644
index 6f850c8..44b1f02 100644
--- a/Data/Vinyl/SRec.hs
+++ b/Data/Vinyl/SRec.hs
@@ -25,6 +25,7 @@
......@@ -63,6 +63,15 @@ index 6f850c8..68c6893 100644
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ConstraintKinds #-}
@@ -74,7 +75,7 @@ import GHC.Base (realWorld#)
import GHC.TypeLits (Symbol)
import GHC.Prim (MutableByteArray#, newAlignedPinnedByteArray#, byteArrayContents#)
-import GHC.Prim (unsafeCoerce#, touch#, RealWorld)
+import GHC.Exts (unsafeCoerce#, touch#, RealWorld)
import GHC.Ptr (Ptr(..))
import GHC.Types (Int(..))
@@ -218,8 +219,14 @@ mallocAndCopy src n = do
withForeignPtr dst $ \dst' ->
dst <$ copyBytes dst' src' n
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment