diff options
author | Krzysztof Gogolewski <krzysztof.gogolewski@tweag.io> | 2022-03-30 21:11:54 +0200 |
---|---|---|
committer | Matthew Pickering <matthewtpickering@gmail.com> | 2022-04-01 11:14:08 +0100 |
commit | f8f152e7089af9a5434408e17ff071999d381ee1 (patch) | |
tree | d00356e813c0fd95dbf81b796798f35fbe46e32a /testsuite/tests | |
parent | 691508d87ec089e46524461a5c6ec59b1c17be4c (diff) | |
download | haskell-f8f152e7089af9a5434408e17ff071999d381ee1.tar.gz |
Change GHC.Prim to GHC.Exts in docs and tests
Users are supposed to import GHC.Exts rather than GHC.Prim.
Part of #18749.
Diffstat (limited to 'testsuite/tests')
110 files changed, 89 insertions, 113 deletions
diff --git a/testsuite/tests/backpack/should_compile/bkp16.bkp b/testsuite/tests/backpack/should_compile/bkp16.bkp index f1a161e53c..d61184c499 100644 --- a/testsuite/tests/backpack/should_compile/bkp16.bkp +++ b/testsuite/tests/backpack/should_compile/bkp16.bkp @@ -2,7 +2,7 @@ unit p where dependency ghc-prim signature Int where - import GHC.Prim + import GHC.Exts data Int = I# Int# unit q where dependency p[Int=base:GHC.Exts] diff --git a/testsuite/tests/backpack/should_run/T13955.bkp b/testsuite/tests/backpack/should_run/T13955.bkp index eadeee6f5c..f469076dd7 100644 --- a/testsuite/tests/backpack/should_run/T13955.bkp +++ b/testsuite/tests/backpack/should_run/T13955.bkp @@ -28,7 +28,7 @@ unit number-int where unit number-unboxed-int where module NumberUnknown where import GHC.Types - import GHC.Prim + import GHC.Exts type Rep = IntRep type Number = Int# plus :: Int# -> Int# -> Int# diff --git a/testsuite/tests/backpack/should_run/T20133.bkp b/testsuite/tests/backpack/should_run/T20133.bkp index 304f857ae9..557d1f2f7c 100644 --- a/testsuite/tests/backpack/should_run/T20133.bkp +++ b/testsuite/tests/backpack/should_run/T20133.bkp @@ -18,7 +18,7 @@ unit number-unknown where unit number-unboxed-int where module NumberUnknown where import GHC.Types - import GHC.Prim + import GHC.Exts type Rep a = IntRep type Number a = Int# plus :: Int# -> Int# -> Int# diff --git a/testsuite/tests/codeGen/should_compile/T12115.hs b/testsuite/tests/codeGen/should_compile/T12115.hs index bc119e58b4..87a96c3ade 100644 --- a/testsuite/tests/codeGen/should_compile/T12115.hs +++ b/testsuite/tests/codeGen/should_compile/T12115.hs @@ -2,7 +2,7 @@ module T12115 where -import GHC.Prim +import GHC.Exts import GHC.Types f :: (# (# #), (# #) #) -> String diff --git a/testsuite/tests/codeGen/should_compile/T12355.hs b/testsuite/tests/codeGen/should_compile/T12355.hs index 9ad9ebea90..534b8963c0 100644 --- a/testsuite/tests/codeGen/should_compile/T12355.hs +++ b/testsuite/tests/codeGen/should_compile/T12355.hs @@ -2,6 +2,6 @@ module Lib where -import GHC.Prim +import GHC.Exts foreign import prim f1 :: Int# -> Int# diff --git a/testsuite/tests/codeGen/should_run/CopySmallArray.hs b/testsuite/tests/codeGen/should_run/CopySmallArray.hs index 6902fe2db2..e3a5143ac8 100644 --- a/testsuite/tests/codeGen/should_run/CopySmallArray.hs +++ b/testsuite/tests/codeGen/should_run/CopySmallArray.hs @@ -6,7 +6,6 @@ module Main ( main ) where import GHC.Exts hiding (IsList(..)) -import GHC.Prim import GHC.ST main :: IO () diff --git a/testsuite/tests/codeGen/should_run/SizeOfSmallArray.hs b/testsuite/tests/codeGen/should_run/SizeOfSmallArray.hs index 2e62709748..ad5b26c650 100644 --- a/testsuite/tests/codeGen/should_run/SizeOfSmallArray.hs +++ b/testsuite/tests/codeGen/should_run/SizeOfSmallArray.hs @@ -3,7 +3,6 @@ module Main ( main ) where import GHC.Exts -import GHC.Prim import GHC.ST main = putStr diff --git a/testsuite/tests/codeGen/should_run/T15696_1.hs b/testsuite/tests/codeGen/should_run/T15696_1.hs index e747c0ad16..a3b53d4b24 100644 --- a/testsuite/tests/codeGen/should_run/T15696_1.hs +++ b/testsuite/tests/codeGen/should_run/T15696_1.hs @@ -1,7 +1,6 @@ {-# LANGUAGE MagicHash #-} import GHC.Exts -import GHC.Prim main :: IO () main = print (cmpT a T2) diff --git a/testsuite/tests/codeGen/should_run/T15696_2.hs b/testsuite/tests/codeGen/should_run/T15696_2.hs index 1a404bee92..bb17e3bc71 100644 --- a/testsuite/tests/codeGen/should_run/T15696_2.hs +++ b/testsuite/tests/codeGen/should_run/T15696_2.hs @@ -1,7 +1,6 @@ {-# LANGUAGE MagicHash #-} import GHC.Exts -import GHC.Prim main :: IO () main = do diff --git a/testsuite/tests/codeGen/should_run/T16449_2.hs b/testsuite/tests/codeGen/should_run/T16449_2.hs index de461ab438..4eee64e70d 100644 --- a/testsuite/tests/codeGen/should_run/T16449_2.hs +++ b/testsuite/tests/codeGen/should_run/T16449_2.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Int -- Test that large unchecked shifts, which constitute undefined behavior, do diff --git a/testsuite/tests/codeGen/should_run/T8256.hs b/testsuite/tests/codeGen/should_run/T8256.hs index d9dbd25b9c..5af51d6be5 100644 --- a/testsuite/tests/codeGen/should_run/T8256.hs +++ b/testsuite/tests/codeGen/should_run/T8256.hs @@ -3,7 +3,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types import Foreign import Foreign.Ptr diff --git a/testsuite/tests/codeGen/should_run/T9013.hs b/testsuite/tests/codeGen/should_run/T9013.hs index 35c074e68d..2bc821002c 100644 --- a/testsuite/tests/codeGen/should_run/T9013.hs +++ b/testsuite/tests/codeGen/should_run/T9013.hs @@ -1,6 +1,6 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim +import GHC.Exts import GHC.Word big :: Word diff --git a/testsuite/tests/codeGen/should_run/cas_int.hs b/testsuite/tests/codeGen/should_run/cas_int.hs index f3c0bd0137..dc2bd4507d 100644 --- a/testsuite/tests/codeGen/should_run/cas_int.hs +++ b/testsuite/tests/codeGen/should_run/cas_int.hs @@ -12,7 +12,7 @@ module Main ( main ) where import Data.Bits import GHC.Int -import GHC.Prim +import GHC.Exts import GHC.Word import Control.Monad import Control.Concurrent diff --git a/testsuite/tests/codeGen/should_run/cgrun064.hs b/testsuite/tests/codeGen/should_run/cgrun064.hs index 527c6bde67..3c071afb9f 100644 --- a/testsuite/tests/codeGen/should_run/cgrun064.hs +++ b/testsuite/tests/codeGen/should_run/cgrun064.hs @@ -6,7 +6,6 @@ module Main ( main ) where import GHC.Exts hiding (IsList(..)) -import GHC.Prim import GHC.ST main :: IO () diff --git a/testsuite/tests/codeGen/should_run/cgrun065.hs b/testsuite/tests/codeGen/should_run/cgrun065.hs index 6934832013..1c6f3589bf 100644 --- a/testsuite/tests/codeGen/should_run/cgrun065.hs +++ b/testsuite/tests/codeGen/should_run/cgrun065.hs @@ -3,7 +3,6 @@ module Main ( main ) where import GHC.Exts -import GHC.Prim import GHC.ST main = putStr diff --git a/testsuite/tests/codeGen/should_run/cgrun070.hs b/testsuite/tests/codeGen/should_run/cgrun070.hs index d37032a707..6d16141202 100644 --- a/testsuite/tests/codeGen/should_run/cgrun070.hs +++ b/testsuite/tests/codeGen/should_run/cgrun070.hs @@ -7,7 +7,6 @@ module Main ( main ) where import GHC.Word import GHC.Exts hiding (IsList(..)) -import GHC.Prim import GHC.ST import GHC.IO import GHC.Ptr diff --git a/testsuite/tests/codeGen/should_run/cgrun071.hs b/testsuite/tests/codeGen/should_run/cgrun071.hs index 21ee04121b..70a605fd2f 100644 --- a/testsuite/tests/codeGen/should_run/cgrun071.hs +++ b/testsuite/tests/codeGen/should_run/cgrun071.hs @@ -3,7 +3,7 @@ module Main ( main ) where import Data.Bits -import GHC.Prim +import GHC.Exts import GHC.Word #include "MachDeps.h" diff --git a/testsuite/tests/codeGen/should_run/cgrun072.hs b/testsuite/tests/codeGen/should_run/cgrun072.hs index b97ce56d01..2d7e90f115 100644 --- a/testsuite/tests/codeGen/should_run/cgrun072.hs +++ b/testsuite/tests/codeGen/should_run/cgrun072.hs @@ -14,7 +14,7 @@ module Main ( main ) where import Data.Bits -import GHC.Prim +import GHC.Exts import GHC.Word #include "MachDeps.h" diff --git a/testsuite/tests/codeGen/should_run/cgrun075.hs b/testsuite/tests/codeGen/should_run/cgrun075.hs index 5babde1254..6dcbda04c7 100644 --- a/testsuite/tests/codeGen/should_run/cgrun075.hs +++ b/testsuite/tests/codeGen/should_run/cgrun075.hs @@ -4,7 +4,7 @@ module Main ( main ) where import Data.Bits import GHC.Int -import GHC.Prim +import GHC.Exts import GHC.Word import Data.Int import Data.Word diff --git a/testsuite/tests/codeGen/should_run/cgrun076.hs b/testsuite/tests/codeGen/should_run/cgrun076.hs index 4779b5beb8..7721183ec1 100644 --- a/testsuite/tests/codeGen/should_run/cgrun076.hs +++ b/testsuite/tests/codeGen/should_run/cgrun076.hs @@ -4,7 +4,7 @@ module Main ( main ) where import Data.Bits import GHC.Int -import GHC.Prim +import GHC.Exts import GHC.Word import Data.Int import Data.Word diff --git a/testsuite/tests/codeGen/should_run/cgrun077.hs b/testsuite/tests/codeGen/should_run/cgrun077.hs index fa224e9eca..965b86214b 100644 --- a/testsuite/tests/codeGen/should_run/cgrun077.hs +++ b/testsuite/tests/codeGen/should_run/cgrun077.hs @@ -3,7 +3,7 @@ module Main ( main ) where import Data.Bits -import GHC.Prim +import GHC.Exts import GHC.Word #include "MachDeps.h" diff --git a/testsuite/tests/codeGen/should_run/cgrun079.hs b/testsuite/tests/codeGen/should_run/cgrun079.hs index e299c860c3..80fea2cc2c 100644 --- a/testsuite/tests/codeGen/should_run/cgrun079.hs +++ b/testsuite/tests/codeGen/should_run/cgrun079.hs @@ -5,7 +5,7 @@ module Main ( main ) where import Data.Bits import GHC.Int -import GHC.Prim +import GHC.Exts import GHC.Word import Control.Monad diff --git a/testsuite/tests/codeGen/should_run/cgrun080.hs b/testsuite/tests/codeGen/should_run/cgrun080.hs index 78d54700f9..7c40450ea9 100644 --- a/testsuite/tests/codeGen/should_run/cgrun080.hs +++ b/testsuite/tests/codeGen/should_run/cgrun080.hs @@ -10,7 +10,7 @@ module Main ( main ) where import Data.Bits import GHC.Int -import GHC.Prim +import GHC.Exts import GHC.Word import Control.Monad import Control.Concurrent diff --git a/testsuite/tests/codeGen/should_run/compareByteArrays.hs b/testsuite/tests/codeGen/should_run/compareByteArrays.hs index 5bd0e58588..7131b27914 100644 --- a/testsuite/tests/codeGen/should_run/compareByteArrays.hs +++ b/testsuite/tests/codeGen/should_run/compareByteArrays.hs @@ -9,8 +9,7 @@ module Main (main) where import Control.Monad import Control.Monad.ST import Data.List (sort, intercalate) -import GHC.Exts (Int (..)) -import GHC.Prim +import GHC.Exts import GHC.ST (ST (ST)) import GHC.Word (Word8 (..)) import Text.Printf diff --git a/testsuite/tests/concurrent/should_run/T367_letnoescape.hs b/testsuite/tests/concurrent/should_run/T367_letnoescape.hs index 5230509e71..0e91ea693a 100644 --- a/testsuite/tests/concurrent/should_run/T367_letnoescape.hs +++ b/testsuite/tests/concurrent/should_run/T367_letnoescape.hs @@ -4,7 +4,6 @@ import Control.Concurrent import GHC.Conc -import GHC.Prim import GHC.Exts main = do diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar001.hs b/testsuite/tests/concurrent/should_run/hs_try_putmvar001.hs index af4eabb263..a16ae482cb 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar001.hs +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar001.hs @@ -6,7 +6,7 @@ import Control.Exception import Foreign import Foreign.C import GHC.Conc -import GHC.Prim +import GHC.Exts -- Sample code demonstrating proper use of hs_try_putmvar() diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar002.hs b/testsuite/tests/concurrent/should_run/hs_try_putmvar002.hs index a8eac42dec..d1130981d6 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar002.hs +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar002.hs @@ -7,7 +7,7 @@ import Control.Monad import Foreign hiding (void) import Foreign.C import GHC.Conc -import GHC.Prim +import GHC.Exts import System.Environment -- Measure raw throughput, for M threads that each do N calls to C diff --git a/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs b/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs index caaadc1aae..6677207665 100644 --- a/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs +++ b/testsuite/tests/concurrent/should_run/hs_try_putmvar003.hs @@ -8,7 +8,7 @@ import Foreign hiding (void) import Foreign.C import GHC.Conc import GHC.MVar (MVar(..)) -import GHC.Prim +import GHC.Exts import System.Environment import System.Exit import Unsafe.Coerce diff --git a/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs b/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs index a18d75aeef..436c068b29 100644 --- a/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs +++ b/testsuite/tests/concurrent/should_run/setnumcapabilities001.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.Conc -import GHC.Prim +import GHC.Exts import System.Environment import System.IO import Control.Monad diff --git a/testsuite/tests/dependent/should_compile/T15076c.hs b/testsuite/tests/dependent/should_compile/T15076c.hs index b689b5b6f0..948928a8fb 100644 --- a/testsuite/tests/dependent/should_compile/T15076c.hs +++ b/testsuite/tests/dependent/should_compile/T15076c.hs @@ -6,7 +6,7 @@ module Super where import Data.Kind import Data.Proxy -import GHC.Prim +import GHC.Exts class (a ~ b) => C a b data SameKind :: k -> k -> Type where diff --git a/testsuite/tests/dependent/should_fail/T17541.hs b/testsuite/tests/dependent/should_fail/T17541.hs index dcf6e91381..48d9c0c37e 100644 --- a/testsuite/tests/dependent/should_fail/T17541.hs +++ b/testsuite/tests/dependent/should_fail/T17541.hs @@ -9,7 +9,6 @@ TypeFamilyDependencies #-} module T17541 where -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/dependent/should_fail/T17541.stderr b/testsuite/tests/dependent/should_fail/T17541.stderr index d0ea673a2b..2321aee6ed 100644 --- a/testsuite/tests/dependent/should_fail/T17541.stderr +++ b/testsuite/tests/dependent/should_fail/T17541.stderr @@ -1,5 +1,5 @@ -T17541.hs:20:17: error: +T17541.hs:19:17: error: • Couldn't match kind ‘Rep rep’ with ‘'IntRep’ Expected kind ‘TYPE (Rep rep)’, but ‘Int#’ has kind ‘TYPE 'IntRep’ The type variable ‘rep’ is ambiguous diff --git a/testsuite/tests/deriving/perf/T10858.hs b/testsuite/tests/deriving/perf/T10858.hs index b4eb7e8a45..b32f3bc018 100644 --- a/testsuite/tests/deriving/perf/T10858.hs +++ b/testsuite/tests/deriving/perf/T10858.hs @@ -1,6 +1,6 @@ {-# LANGUAGE MagicHash #-} -import GHC.Prim +import GHC.Exts data TestData = First Int Double String Int Int Int Int | Second Char# Int# Word# Double# diff --git a/testsuite/tests/deriving/should_compile/T11174.hs b/testsuite/tests/deriving/should_compile/T11174.hs index c3b2bc711c..cb0a85172d 100644 --- a/testsuite/tests/deriving/should_compile/T11174.hs +++ b/testsuite/tests/deriving/should_compile/T11174.hs @@ -4,7 +4,7 @@ {-# LANGUAGE MagicHash #-} module T11174 where -import GHC.Prim (Int#) +import GHC.Exts (Int#) data IntHash a = IntHash Int# deriving (Functor, Foldable, Traversable) diff --git a/testsuite/tests/deriving/should_fail/T2701.hs b/testsuite/tests/deriving/should_fail/T2701.hs index 0d6dab3fbb..6964ddc44e 100644 --- a/testsuite/tests/deriving/should_fail/T2701.hs +++ b/testsuite/tests/deriving/should_fail/T2701.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, DeriveDataTypeable #-} module T2700 where -import GHC.Prim +import GHC.Exts import Data.Data import Data.Typeable diff --git a/testsuite/tests/deriving/should_run/T10104.hs b/testsuite/tests/deriving/should_run/T10104.hs index 154a6097f7..f22e446353 100644 --- a/testsuite/tests/deriving/should_run/T10104.hs +++ b/testsuite/tests/deriving/should_run/T10104.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module Main where -import GHC.Prim +import GHC.Exts data P = Positives Int# Float# Double# Char# Word# deriving Show data N = Negatives Int# Float# Double# deriving Show diff --git a/testsuite/tests/driver/T10600.hs b/testsuite/tests/driver/T10600.hs index 86b6e6cbfc..3dbce43e4d 100644 --- a/testsuite/tests/driver/T10600.hs +++ b/testsuite/tests/driver/T10600.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module T10600 where -import GHC.Prim +import GHC.Exts -- This shouldn't compile as unlifted bindings aren't allowed at top-level. -- However, #10600 described the situation where an error isn't throw when we diff --git a/testsuite/tests/ffi/should_compile/cc016.hs b/testsuite/tests/ffi/should_compile/cc016.hs index 549dc15c77..5e1125de3f 100644 --- a/testsuite/tests/ffi/should_compile/cc016.hs +++ b/testsuite/tests/ffi/should_compile/cc016.hs @@ -6,7 +6,7 @@ module Cc015 where import Foreign import Foreign.C.Types -import GHC.Prim +import GHC.Exts type family F a type instance F Int = Int# -> Int# diff --git a/testsuite/tests/ffi/should_fail/ccfail001.hs b/testsuite/tests/ffi/should_fail/ccfail001.hs index 0b7d5e8c7f..de3f732787 100644 --- a/testsuite/tests/ffi/should_fail/ccfail001.hs +++ b/testsuite/tests/ffi/should_fail/ccfail001.hs @@ -5,6 +5,6 @@ module Foo where -import GHC.Prim +import GHC.Exts foreign import ccall foo :: Int -> State# RealWorld diff --git a/testsuite/tests/generics/T8468.hs b/testsuite/tests/generics/T8468.hs index f76be9f951..c4292cd970 100644 --- a/testsuite/tests/generics/T8468.hs +++ b/testsuite/tests/generics/T8468.hs @@ -1,7 +1,7 @@ {-# Language DeriveGeneric, MagicHash #-} import GHC.Generics -import GHC.Prim +import GHC.Exts data Array a = Array (Array# a) deriving Generic1 newtype Vec a = MkVec {unVec :: Array a} deriving Generic1 diff --git a/testsuite/tests/ghci/scripts/T12520.hs b/testsuite/tests/ghci/scripts/T12520.hs index cedf5875c4..8d8eb1471a 100644 --- a/testsuite/tests/ghci/scripts/T12520.hs +++ b/testsuite/tests/ghci/scripts/T12520.hs @@ -2,7 +2,7 @@ module Bug ( box, wrap, proxy ) where -import GHC.Prim +import GHC.Exts box :: (# Proxy# a, b #) -> b box (# x, y #) = y diff --git a/testsuite/tests/ghci/should_run/T19733.hs b/testsuite/tests/ghci/should_run/T19733.hs index 7bb8102a2d..25ac106867 100644 --- a/testsuite/tests/ghci/should_run/T19733.hs +++ b/testsuite/tests/ghci/should_run/T19733.hs @@ -6,7 +6,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.IO import Foreign.C diff --git a/testsuite/tests/indexed-types/should_compile/T13244.hs b/testsuite/tests/indexed-types/should_compile/T13244.hs index 6cfea014a4..1fb7d073a0 100644 --- a/testsuite/tests/indexed-types/should_compile/T13244.hs +++ b/testsuite/tests/indexed-types/should_compile/T13244.hs @@ -4,7 +4,7 @@ module T13244 where import Data.Int import Data.Word -import GHC.Prim +import GHC.Exts import GHC.Types type family Rep x where diff --git a/testsuite/tests/llvm/should_compile/T5681.hs b/testsuite/tests/llvm/should_compile/T5681.hs index d1c073a328..a853295516 100644 --- a/testsuite/tests/llvm/should_compile/T5681.hs +++ b/testsuite/tests/llvm/should_compile/T5681.hs @@ -3,7 +3,7 @@ -- Test case for #5681 module Main where -import GHC.Prim +import GHC.Exts work :: Int -> Int work n = work (n-1) diff --git a/testsuite/tests/llvm/should_compile/T7575.hs b/testsuite/tests/llvm/should_compile/T7575.hs index 78b0bd29a8..49e1cd9708 100644 --- a/testsuite/tests/llvm/should_compile/T7575.hs +++ b/testsuite/tests/llvm/should_compile/T7575.hs @@ -2,7 +2,7 @@ {-# LANGUAGE MagicHash, UnliftedFFITypes #-} module T7575 where -import GHC.Prim +import GHC.Exts import GHC.Word import GHC.Types diff --git a/testsuite/tests/llvm/should_compile/T8131b.hs b/testsuite/tests/llvm/should_compile/T8131b.hs index e57d6dcf77..af384da3d6 100644 --- a/testsuite/tests/llvm/should_compile/T8131b.hs +++ b/testsuite/tests/llvm/should_compile/T8131b.hs @@ -1,6 +1,6 @@ {-# LANGUAGE Haskell2010 #-} {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim +import GHC.Exts import GHC.IO main = IO $ \s -> diff --git a/testsuite/tests/module/base01/GHC/Base.hs b/testsuite/tests/module/base01/GHC/Base.hs index 9149f8544b..ef32f89cdd 100644 --- a/testsuite/tests/module/base01/GHC/Base.hs +++ b/testsuite/tests/module/base01/GHC/Base.hs @@ -1,7 +1,6 @@ module GHC.Base (module GHC.Base, Bool(..)) where -import GHC.Prim import GHC.Types default () diff --git a/testsuite/tests/numeric/should_run/CarryOverflow.hs b/testsuite/tests/numeric/should_run/CarryOverflow.hs index 1a543de713..bcbcf121bc 100644 --- a/testsuite/tests/numeric/should_run/CarryOverflow.hs +++ b/testsuite/tests/numeric/should_run/CarryOverflow.hs @@ -1,6 +1,5 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim import GHC.Word import GHC.Exts diff --git a/testsuite/tests/numeric/should_run/add2.hs b/testsuite/tests/numeric/should_run/add2.hs index 5990f4fa83..8aa320dacb 100644 --- a/testsuite/tests/numeric/should_run/add2.hs +++ b/testsuite/tests/numeric/should_run/add2.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim +import GHC.Exts import GHC.Word import Data.Bits diff --git a/testsuite/tests/numeric/should_run/mul2.hs b/testsuite/tests/numeric/should_run/mul2.hs index 82a89d66d0..474e421b40 100644 --- a/testsuite/tests/numeric/should_run/mul2.hs +++ b/testsuite/tests/numeric/should_run/mul2.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim +import GHC.Exts import GHC.Word import Data.Bits diff --git a/testsuite/tests/numeric/should_run/quotRem2.hs b/testsuite/tests/numeric/should_run/quotRem2.hs index bb7fb6cd12..dc302cbac0 100644 --- a/testsuite/tests/numeric/should_run/quotRem2.hs +++ b/testsuite/tests/numeric/should_run/quotRem2.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim +import GHC.Exts import GHC.Word import Control.Monad import Data.Bits diff --git a/testsuite/tests/parser/should_fail/T15209.hs b/testsuite/tests/parser/should_fail/T15209.hs index 1679d80ba6..944b967965 100644 --- a/testsuite/tests/parser/should_fail/T15209.hs +++ b/testsuite/tests/parser/should_fail/T15209.hs @@ -1,7 +1,7 @@ {-# LANGUAGE GADTs, TypeOperators #-} module T15209 where -import GHC.Prim +import GHC.Exts foo :: a ~# Int -> () foo = () diff --git a/testsuite/tests/parser/should_fail/T15209.stderr b/testsuite/tests/parser/should_fail/T15209.stderr index fe1666c37e..23f8876d67 100644 --- a/testsuite/tests/parser/should_fail/T15209.stderr +++ b/testsuite/tests/parser/should_fail/T15209.stderr @@ -1,4 +1,6 @@ T15209.hs:6:10: error: Not in scope: type constructor or class ‘~#’ - Suggested fix: Perhaps use ‘~’ (imported from Prelude) + Suggested fix: + Perhaps use one of these: + ‘~’ (imported from GHC.Exts), ‘~~’ (imported from GHC.Exts) diff --git a/testsuite/tests/polykinds/T12718.hs b/testsuite/tests/polykinds/T12718.hs index 7bbe1d572e..8018e097fa 100644 --- a/testsuite/tests/polykinds/T12718.hs +++ b/testsuite/tests/polykinds/T12718.hs @@ -5,7 +5,7 @@ module Main where import Prelude hiding (Eq (..), Num(..)) import qualified Prelude as P -import GHC.Prim +import GHC.Exts import GHC.Types class XNum (a :: TYPE rep) where diff --git a/testsuite/tests/primops/should_compile/T19851.hs b/testsuite/tests/primops/should_compile/T19851.hs index a3a5dd78fc..934d243ea4 100644 --- a/testsuite/tests/primops/should_compile/T19851.hs +++ b/testsuite/tests/primops/should_compile/T19851.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module T19851 where -import GHC.Prim +import GHC.Exts import GHC.Word diff --git a/testsuite/tests/primops/should_run/ArithInt16.hs b/testsuite/tests/primops/should_run/ArithInt16.hs index 373a61ccd8..297973fe3b 100644 --- a/testsuite/tests/primops/should_run/ArithInt16.hs +++ b/testsuite/tests/primops/should_run/ArithInt16.hs @@ -6,7 +6,6 @@ module Main where import Data.Int import Data.List (findIndex) -import GHC.Prim import GHC.Exts main :: IO () diff --git a/testsuite/tests/primops/should_run/ArithInt32.hs b/testsuite/tests/primops/should_run/ArithInt32.hs index 8d1c6a4ad0..d9a68bc85d 100644 --- a/testsuite/tests/primops/should_run/ArithInt32.hs +++ b/testsuite/tests/primops/should_run/ArithInt32.hs @@ -6,7 +6,6 @@ module Main where import Data.Int import Data.List (findIndex) -import GHC.Prim import GHC.Exts main :: IO () diff --git a/testsuite/tests/primops/should_run/ArithInt8.hs b/testsuite/tests/primops/should_run/ArithInt8.hs index 4629772a7d..2e9ab0a49e 100644 --- a/testsuite/tests/primops/should_run/ArithInt8.hs +++ b/testsuite/tests/primops/should_run/ArithInt8.hs @@ -6,7 +6,6 @@ module Main where import Data.Int import Data.List (findIndex) -import GHC.Prim import GHC.Exts main :: IO () diff --git a/testsuite/tests/primops/should_run/ArithWord16.hs b/testsuite/tests/primops/should_run/ArithWord16.hs index cd64614873..0b38ca7653 100644 --- a/testsuite/tests/primops/should_run/ArithWord16.hs +++ b/testsuite/tests/primops/should_run/ArithWord16.hs @@ -7,7 +7,6 @@ module Main where import Data.Word import Data.Bits import Data.List (findIndex) -import GHC.Prim import GHC.Exts main :: IO () diff --git a/testsuite/tests/primops/should_run/ArithWord32.hs b/testsuite/tests/primops/should_run/ArithWord32.hs index ad0352435e..111d486178 100644 --- a/testsuite/tests/primops/should_run/ArithWord32.hs +++ b/testsuite/tests/primops/should_run/ArithWord32.hs @@ -7,7 +7,6 @@ module Main where import Data.Word import Data.Bits import Data.List (findIndex) -import GHC.Prim import GHC.Exts main :: IO () diff --git a/testsuite/tests/primops/should_run/ArithWord8.hs b/testsuite/tests/primops/should_run/ArithWord8.hs index 6fea314bb2..7bfe7c3979 100644 --- a/testsuite/tests/primops/should_run/ArithWord8.hs +++ b/testsuite/tests/primops/should_run/ArithWord8.hs @@ -7,7 +7,6 @@ module Main where import Data.Word import Data.Bits import Data.List (findIndex) -import GHC.Prim import GHC.Exts main :: IO () diff --git a/testsuite/tests/primops/should_run/CmpInt16.hs b/testsuite/tests/primops/should_run/CmpInt16.hs index 0fdec359d7..b83302fcaa 100644 --- a/testsuite/tests/primops/should_run/CmpInt16.hs +++ b/testsuite/tests/primops/should_run/CmpInt16.hs @@ -5,7 +5,6 @@ module Main where import Data.Int import Data.List (findIndex) -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/primops/should_run/CmpInt32.hs b/testsuite/tests/primops/should_run/CmpInt32.hs index a9b560664b..fc3aeacd83 100644 --- a/testsuite/tests/primops/should_run/CmpInt32.hs +++ b/testsuite/tests/primops/should_run/CmpInt32.hs @@ -5,7 +5,6 @@ module Main where import Data.Int import Data.List (findIndex) -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/primops/should_run/CmpInt8.hs b/testsuite/tests/primops/should_run/CmpInt8.hs index 2bed2000da..4ef9f360a4 100644 --- a/testsuite/tests/primops/should_run/CmpInt8.hs +++ b/testsuite/tests/primops/should_run/CmpInt8.hs @@ -5,7 +5,6 @@ module Main where import Data.Int import Data.List (findIndex) -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/primops/should_run/CmpWord16.hs b/testsuite/tests/primops/should_run/CmpWord16.hs index a5d527afd0..53560faa0d 100644 --- a/testsuite/tests/primops/should_run/CmpWord16.hs +++ b/testsuite/tests/primops/should_run/CmpWord16.hs @@ -5,7 +5,6 @@ module Main where import Data.Word import Data.List (findIndex) -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/primops/should_run/CmpWord32.hs b/testsuite/tests/primops/should_run/CmpWord32.hs index aeb7ec28e4..b08d0d342f 100644 --- a/testsuite/tests/primops/should_run/CmpWord32.hs +++ b/testsuite/tests/primops/should_run/CmpWord32.hs @@ -5,7 +5,6 @@ module Main where import Data.Word import Data.List (findIndex) -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/primops/should_run/CmpWord8.hs b/testsuite/tests/primops/should_run/CmpWord8.hs index 813ae7c270..85e95ab233 100644 --- a/testsuite/tests/primops/should_run/CmpWord8.hs +++ b/testsuite/tests/primops/should_run/CmpWord8.hs @@ -5,7 +5,6 @@ module Main where import Data.Word import Data.List (findIndex) -import GHC.Prim import GHC.Exts diff --git a/testsuite/tests/primops/should_run/T10678.hs b/testsuite/tests/primops/should_run/T10678.hs index 9019ab6345..3321d656f5 100644 --- a/testsuite/tests/primops/should_run/T10678.hs +++ b/testsuite/tests/primops/should_run/T10678.hs @@ -1,6 +1,6 @@ {-# LANGUAGE MagicHash #-} -import GHC.Prim +import GHC.Exts main :: IO () main = go 1000000# 10 (2^100) diff --git a/testsuite/tests/printer/Ppr041.hs b/testsuite/tests/printer/Ppr041.hs index 154a6097f7..f22e446353 100644 --- a/testsuite/tests/printer/Ppr041.hs +++ b/testsuite/tests/printer/Ppr041.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module Main where -import GHC.Prim +import GHC.Exts data P = Positives Int# Float# Double# Char# Word# deriving Show data N = Negatives Int# Float# Double# deriving Show diff --git a/testsuite/tests/printer/Test12417.hs b/testsuite/tests/printer/Test12417.hs index 67da7f2107..b991f59f40 100644 --- a/testsuite/tests/printer/Test12417.hs +++ b/testsuite/tests/printer/Test12417.hs @@ -2,7 +2,7 @@ module Test12417 where -import GHC.Prim +import GHC.Exts import GHC.Types import System.Mem (performMajorGC) diff --git a/testsuite/tests/profiling/should_compile/prof-late-cc.hs b/testsuite/tests/profiling/should_compile/prof-late-cc.hs index 9ae777e023..02209efde6 100644 --- a/testsuite/tests/profiling/should_compile/prof-late-cc.hs +++ b/testsuite/tests/profiling/should_compile/prof-late-cc.hs @@ -2,7 +2,7 @@ {-# LANGUAGE NoImplicitPrelude #-} module Test where -import GHC.Prim +import GHC.Exts import GHC.Types -- This caused problems during implementation. diff --git a/testsuite/tests/profiling/should_run/T11627b.hs b/testsuite/tests/profiling/should_run/T11627b.hs index 5e5545a4eb..2368f91f41 100644 --- a/testsuite/tests/profiling/should_run/T11627b.hs +++ b/testsuite/tests/profiling/should_run/T11627b.hs @@ -5,7 +5,7 @@ -- A reduced test case for #11627 -import GHC.Prim +import GHC.Exts import GHC.Types (Int(..),IO(..)) import System.Mem diff --git a/testsuite/tests/rep-poly/RepPolyBackpack4.bkp b/testsuite/tests/rep-poly/RepPolyBackpack4.bkp index 8f151278cb..3a96f1b42e 100644 --- a/testsuite/tests/rep-poly/RepPolyBackpack4.bkp +++ b/testsuite/tests/rep-poly/RepPolyBackpack4.bkp @@ -26,7 +26,7 @@ unit number-int where unit number-unboxed-int where module NumberUnknown where import GHC.Types - import GHC.Prim + import GHC.Exts type Rep = IntRep type Number = Int# plus :: Int# -> Int# -> Int# diff --git a/testsuite/tests/rep-poly/T12709.hs b/testsuite/tests/rep-poly/T12709.hs index 6a7e37a5d2..397dcd7d2c 100644 --- a/testsuite/tests/rep-poly/T12709.hs +++ b/testsuite/tests/rep-poly/T12709.hs @@ -6,7 +6,7 @@ module T12709 where import GHC.Types import Prelude hiding (Num (..)) import qualified Prelude as P -import GHC.Prim +import GHC.Exts data BoxUnbox = BUB Int Int# diff --git a/testsuite/tests/rts/T14900.hs b/testsuite/tests/rts/T14900.hs index bd29289e19..613f66d3a9 100644 --- a/testsuite/tests/rts/T14900.hs +++ b/testsuite/tests/rts/T14900.hs @@ -2,7 +2,7 @@ import GHC.Compact import GHC.Int -import GHC.Prim +import GHC.Exts import GHC.IO import GHC.Exts diff --git a/testsuite/tests/rts/T17088.hs b/testsuite/tests/rts/T17088.hs index 6ca24d88d4..6d7aadc749 100644 --- a/testsuite/tests/rts/T17088.hs +++ b/testsuite/tests/rts/T17088.hs @@ -6,7 +6,7 @@ module Main (main) where import Data.Word import Foreign.Storable -import GHC.Prim +import GHC.Exts import GHC.Ptr import GHC.Types import System.IO.Unsafe diff --git a/testsuite/tests/rts/cloneMyStack.hs b/testsuite/tests/rts/cloneMyStack.hs index 11a69201e0..9de6c359e7 100644 --- a/testsuite/tests/rts/cloneMyStack.hs +++ b/testsuite/tests/rts/cloneMyStack.hs @@ -2,7 +2,7 @@ {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedFFITypes #-} -import GHC.Prim (StackSnapshot#) +import GHC.Exts (StackSnapshot#) import GHC.Stack.CloneStack import Foreign import Foreign.C.Types (CUInt) diff --git a/testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs b/testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs index cccc8ec618..0fe4c291c1 100644 --- a/testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs +++ b/testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs @@ -8,7 +8,7 @@ module Main where import Control.Concurrent import Data.IORef import GHC.IO.Unsafe -import GHC.Prim (StackSnapshot#) +import GHC.Exts (StackSnapshot#) import GHC.Stack.CloneStack import System.Mem diff --git a/testsuite/tests/rts/cloneThreadStack.hs b/testsuite/tests/rts/cloneThreadStack.hs index fa2bc66795..1cd5107892 100644 --- a/testsuite/tests/rts/cloneThreadStack.hs +++ b/testsuite/tests/rts/cloneThreadStack.hs @@ -2,7 +2,7 @@ {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnliftedFFITypes #-} -import GHC.Prim (StackSnapshot#, ThreadId#) +import GHC.Exts (StackSnapshot#, ThreadId#) import GHC.Conc.Sync (ThreadId(..)) import GHC.Stack.CloneStack import Control.Concurrent diff --git a/testsuite/tests/simplCore/T9646/Type.hs b/testsuite/tests/simplCore/T9646/Type.hs index 337a7859cc..4de77648ce 100644 --- a/testsuite/tests/simplCore/T9646/Type.hs +++ b/testsuite/tests/simplCore/T9646/Type.hs @@ -4,7 +4,7 @@ module Type where -import GHC.Prim +import GHC.Exts import GHC.Types import StrictPrim diff --git a/testsuite/tests/simplCore/should_compile/T13155.hs b/testsuite/tests/simplCore/should_compile/T13155.hs index f3ec2c8e50..fd968c6239 100644 --- a/testsuite/tests/simplCore/should_compile/T13155.hs +++ b/testsuite/tests/simplCore/should_compile/T13155.hs @@ -4,7 +4,6 @@ module T13155 where import GHC.Ptr -import GHC.Prim import GHC.Exts foo :: Ptr Float -> State# RealWorld -> (# State# RealWorld, Float #) diff --git a/testsuite/tests/simplCore/should_compile/T18589.hs b/testsuite/tests/simplCore/should_compile/T18589.hs index c892bc844e..82c6723730 100644 --- a/testsuite/tests/simplCore/should_compile/T18589.hs +++ b/testsuite/tests/simplCore/should_compile/T18589.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module T18589 where -import GHC.Prim +import GHC.Exts -- See Note [Guarding against silly shifts] -- Make sure that a silly shift is optimized correctly diff --git a/testsuite/tests/simplCore/should_compile/T5658b.hs b/testsuite/tests/simplCore/should_compile/T5658b.hs index baaea86640..7b42738395 100644 --- a/testsuite/tests/simplCore/should_compile/T5658b.hs +++ b/testsuite/tests/simplCore/should_compile/T5658b.hs @@ -1,7 +1,6 @@ {-# LANGUAGE MagicHash, BangPatterns #-} module T5658b where -import GHC.Prim -import GHC.Exts ( isTrue# ) +import GHC.Exts foo :: ByteArray# -> ByteArray# -> Int# -> Int# -> Bool foo xs ys m n = go 0# 0# diff --git a/testsuite/tests/simplCore/should_compile/T7088.hs b/testsuite/tests/simplCore/should_compile/T7088.hs index 7b3ec2c603..254d7851fa 100644 --- a/testsuite/tests/simplCore/should_compile/T7088.hs +++ b/testsuite/tests/simplCore/should_compile/T7088.hs @@ -2,7 +2,7 @@ module Float where -import GHC.Prim +import GHC.Exts foo vs = let w = if length (reverse vs) > 10 then Just (length vs) else Nothing diff --git a/testsuite/tests/simplCore/should_compile/T7287.hs b/testsuite/tests/simplCore/should_compile/T7287.hs index bb9035a6ae..e8dc1bda11 100644 --- a/testsuite/tests/simplCore/should_compile/T7287.hs +++ b/testsuite/tests/simplCore/should_compile/T7287.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module T7287 where -import GHC.Prim +import GHC.Exts {-# RULES "int2Word#/word2Int#" forall x. int2Word# (word2Int# x) = x diff --git a/testsuite/tests/simplCore/should_compile/T7796.hs b/testsuite/tests/simplCore/should_compile/T7796.hs index f0f5353316..6d6c824332 100644 --- a/testsuite/tests/simplCore/should_compile/T7796.hs +++ b/testsuite/tests/simplCore/should_compile/T7796.hs @@ -2,7 +2,7 @@ module T7796 where -import GHC.Prim +import GHC.Exts -- -- test for #7796 diff --git a/testsuite/tests/simplCore/should_compile/T8274.hs b/testsuite/tests/simplCore/should_compile/T8274.hs index 03f50ef3ea..97a1cde04c 100644 --- a/testsuite/tests/simplCore/should_compile/T8274.hs +++ b/testsuite/tests/simplCore/should_compile/T8274.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module T8274 where -import GHC.Prim +import GHC.Exts data P = Positives Int# Float# Double# Char# Word# data N = Negatives Int# Float# Double# diff --git a/testsuite/tests/simplCore/should_run/T9390.hs b/testsuite/tests/simplCore/should_run/T9390.hs index 04b4da0e4d..2d5d9ce6e4 100644 --- a/testsuite/tests/simplCore/should_run/T9390.hs +++ b/testsuite/tests/simplCore/should_run/T9390.hs @@ -2,7 +2,7 @@ module Main(main ) where import GHC.IO (IO (..)) -import GHC.Prim +import GHC.Exts writeB :: MutableArray# RealWorld Char -> IO () writeB arr# = IO $ \s0# -> (# writeArray# arr# 0# 'B' s0#, () #) diff --git a/testsuite/tests/simplCore/should_run/simplrun010.hs b/testsuite/tests/simplCore/should_run/simplrun010.hs index eeeb48281f..eb9d18973d 100644 --- a/testsuite/tests/simplCore/should_run/simplrun010.hs +++ b/testsuite/tests/simplCore/should_run/simplrun010.hs @@ -17,7 +17,7 @@ import Data.Char(ord,chr) -- low level imports import GHC.Base (realWorld#) import GHC.IO (IO(IO), unIO, unsafePerformIO) -import GHC.Prim (State#,RealWorld) +import GHC.Exts (State#,RealWorld) -- FFI replacements for Haskell stuff diff --git a/testsuite/tests/stranal/should_compile/T13031.hs b/testsuite/tests/stranal/should_compile/T13031.hs index d5fe761b34..99b714b5a1 100644 --- a/testsuite/tests/stranal/should_compile/T13031.hs +++ b/testsuite/tests/stranal/should_compile/T13031.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash #-} module Foo( f ) where -import GHC.Prim +import GHC.Exts f True = raise# True f False = \p q -> raise# False diff --git a/testsuite/tests/th/TH_StringPrimL.hs b/testsuite/tests/th/TH_StringPrimL.hs index 92f791fb56..7a88e8b63e 100644 --- a/testsuite/tests/th/TH_StringPrimL.hs +++ b/testsuite/tests/th/TH_StringPrimL.hs @@ -2,7 +2,7 @@ module Main where import Language.Haskell.TH -import GHC.Prim(Addr#) +import GHC.Exts(Addr#) import GHC.Ptr import Foreign.Marshal.Array (peekArray) import Data.Word (Word8) diff --git a/testsuite/tests/th/TH_foreignCallingConventions.hs b/testsuite/tests/th/TH_foreignCallingConventions.hs index ee39510169..66548b91bb 100644 --- a/testsuite/tests/th/TH_foreignCallingConventions.hs +++ b/testsuite/tests/th/TH_foreignCallingConventions.hs @@ -4,7 +4,7 @@ module TH_foreignCallingConventions where -import GHC.Prim +import GHC.Exts import Control.Applicative import Language.Haskell.TH import System.IO diff --git a/testsuite/tests/typecheck/should_compile/T14185.hs b/testsuite/tests/typecheck/should_compile/T14185.hs index 41e47d2913..7d1152fc33 100644 --- a/testsuite/tests/typecheck/should_compile/T14185.hs +++ b/testsuite/tests/typecheck/should_compile/T14185.hs @@ -4,7 +4,7 @@ module T14185 where import GHC.Types -import GHC.Prim +import GHC.Exts class Unbox (t :: *) (r :: TYPE k) | t -> r, r -> t where diff --git a/testsuite/tests/typecheck/should_compile/T7888.hs b/testsuite/tests/typecheck/should_compile/T7888.hs index de9792784a..ba979e5cbc 100644 --- a/testsuite/tests/typecheck/should_compile/T7888.hs +++ b/testsuite/tests/typecheck/should_compile/T7888.hs @@ -2,7 +2,7 @@ module T7888 where import GHC.Err( undefined ) -import GHC.Prim +import GHC.Exts {- The fix for #11431 makes this no longer work. But it shouldn't really, without impredicativity. diff --git a/testsuite/tests/typecheck/should_fail/T12373.hs b/testsuite/tests/typecheck/should_fail/T12373.hs index 3f23779b82..22867a8dc6 100644 --- a/testsuite/tests/typecheck/should_fail/T12373.hs +++ b/testsuite/tests/typecheck/should_fail/T12373.hs @@ -3,7 +3,7 @@ module T12373 where import GHC.MVar -import GHC.Prim +import GHC.Exts import GHC.Types main :: IO () diff --git a/testsuite/tests/typecheck/should_fail/T13610.hs b/testsuite/tests/typecheck/should_fail/T13610.hs index 371c3388e9..bee75b8faa 100644 --- a/testsuite/tests/typecheck/should_fail/T13610.hs +++ b/testsuite/tests/typecheck/should_fail/T13610.hs @@ -2,7 +2,7 @@ module T13610 where -import GHC.Prim +import GHC.Exts import GHC.Types main = do diff --git a/testsuite/tests/typecheck/should_fail/T13611.hs b/testsuite/tests/typecheck/should_fail/T13611.hs index ea22791dab..9bc894af59 100644 --- a/testsuite/tests/typecheck/should_fail/T13611.hs +++ b/testsuite/tests/typecheck/should_fail/T13611.hs @@ -1,5 +1,5 @@ {-# LANGUAGE MagicHash, UnboxedTuples #-} -import GHC.Prim +import GHC.Exts import GHC.Types main = do diff --git a/testsuite/tests/typecheck/should_fail/T13821A.hs-boot b/testsuite/tests/typecheck/should_fail/T13821A.hs-boot index 4fda6bce21..4406ae4fb7 100644 --- a/testsuite/tests/typecheck/should_fail/T13821A.hs-boot +++ b/testsuite/tests/typecheck/should_fail/T13821A.hs-boot @@ -1,6 +1,6 @@ {-# LANGUAGE MagicHash #-} module T13821A where -import GHC.Prim +import GHC.Exts x :: Int# diff --git a/testsuite/tests/typecheck/should_fail/T13821B.bkp b/testsuite/tests/typecheck/should_fail/T13821B.bkp index 8d5e066c04..238ad6e9ab 100644 --- a/testsuite/tests/typecheck/should_fail/T13821B.bkp +++ b/testsuite/tests/typecheck/should_fail/T13821B.bkp @@ -1,6 +1,6 @@ {-# LANGUAGE MagicHash #-} unit T13821B where signature A where - import GHC.Prim + import GHC.Exts - x :: Int#
\ No newline at end of file + x :: Int# diff --git a/testsuite/tests/typecheck/should_fail/T14605.hs b/testsuite/tests/typecheck/should_fail/T14605.hs index 4f75d59ebd..907b8f65a3 100644 --- a/testsuite/tests/typecheck/should_fail/T14605.hs +++ b/testsuite/tests/typecheck/should_fail/T14605.hs @@ -9,6 +9,6 @@ module T14605 where -import GHC.Prim (coerce) +import GHC.Exts (coerce) duplicate = coerce @(forall x. ()) @(forall x. x) diff --git a/testsuite/tests/typecheck/should_fail/tcfail075.hs b/testsuite/tests/typecheck/should_fail/tcfail075.hs index d9189bf18c..b964fe7b37 100644 --- a/testsuite/tests/typecheck/should_fail/tcfail075.hs +++ b/testsuite/tests/typecheck/should_fail/tcfail075.hs @@ -5,7 +5,7 @@ module ShouldFail where import GHC.Base -import GHC.Prim +import GHC.Exts x = 1# diff --git a/testsuite/tests/typecheck/should_run/T11120.hs b/testsuite/tests/typecheck/should_run/T11120.hs index 5b5d7f343c..12dc5e2791 100644 --- a/testsuite/tests/typecheck/should_run/T11120.hs +++ b/testsuite/tests/typecheck/should_run/T11120.hs @@ -1,7 +1,7 @@ {-# LANGUAGE MagicHash, DataKinds #-} -- See also TypeOf.hs -import GHC.Prim +import GHC.Exts import Data.Typeable data CharHash = CharHash Char# diff --git a/testsuite/tests/typecheck/should_run/tcrun048.hs b/testsuite/tests/typecheck/should_run/tcrun048.hs index 57308c3aaa..df9a6f0f0c 100644 --- a/testsuite/tests/typecheck/should_run/tcrun048.hs +++ b/testsuite/tests/typecheck/should_run/tcrun048.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim (Int#, Double#) +import GHC.Exts (Int#, Double#) main :: IO () main = let f = int2Integer# 0# in putStrLn "" diff --git a/testsuite/tests/unboxedsums/unboxedsums1.hs b/testsuite/tests/unboxedsums/unboxedsums1.hs index 42a04ae94e..78d35b7170 100644 --- a/testsuite/tests/unboxedsums/unboxedsums1.hs +++ b/testsuite/tests/unboxedsums/unboxedsums1.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types import System.Mem (performMajorGC) diff --git a/testsuite/tests/unboxedsums/unboxedsums12.hs b/testsuite/tests/unboxedsums/unboxedsums12.hs index 93f1793e8a..a9ae2efa5f 100644 --- a/testsuite/tests/unboxedsums/unboxedsums12.hs +++ b/testsuite/tests/unboxedsums/unboxedsums12.hs @@ -2,7 +2,7 @@ module Lib where -import GHC.Prim +import GHC.Exts data B = B1 Int# Int# Int# Int# Int# | B2 Float# diff --git a/testsuite/tests/unboxedsums/unboxedsums2.hs b/testsuite/tests/unboxedsums/unboxedsums2.hs index 115415f7c6..ae05b5c386 100644 --- a/testsuite/tests/unboxedsums/unboxedsums2.hs +++ b/testsuite/tests/unboxedsums/unboxedsums2.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types -- Code generator used to fail with illegal instruction errors when Float# is diff --git a/testsuite/tests/unboxedsums/unboxedsums3.hs b/testsuite/tests/unboxedsums/unboxedsums3.hs index add8aa73df..096e0a70f1 100644 --- a/testsuite/tests/unboxedsums/unboxedsums3.hs +++ b/testsuite/tests/unboxedsums/unboxedsums3.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types import Data.Void (Void) diff --git a/testsuite/tests/unboxedsums/unboxedsums6.hs b/testsuite/tests/unboxedsums/unboxedsums6.hs index 767366d4d5..78c9f39350 100644 --- a/testsuite/tests/unboxedsums/unboxedsums6.hs +++ b/testsuite/tests/unboxedsums/unboxedsums6.hs @@ -4,7 +4,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types import System.Mem (performMajorGC) diff --git a/testsuite/tests/unboxedsums/unboxedsums7.hs b/testsuite/tests/unboxedsums/unboxedsums7.hs index d64dabb13a..901ba4004d 100644 --- a/testsuite/tests/unboxedsums/unboxedsums7.hs +++ b/testsuite/tests/unboxedsums/unboxedsums7.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types type Either1 a b c = (# a | (# b, c #) #) diff --git a/testsuite/tests/unboxedsums/unboxedsums8.hs b/testsuite/tests/unboxedsums/unboxedsums8.hs index 07ef122b69..8a7344c950 100644 --- a/testsuite/tests/unboxedsums/unboxedsums8.hs +++ b/testsuite/tests/unboxedsums/unboxedsums8.hs @@ -2,7 +2,7 @@ module Main where -import GHC.Prim +import GHC.Exts import GHC.Types type Sum1 = (# (# Int#, Int #) | (# Int#, Int# #) | (# Int, Int# #) #) |