summaryrefslogtreecommitdiff
path: root/libraries/ghc-prim
diff options
context:
space:
mode:
authorSylvain Henry <sylvain@haskus.fr>2020-04-22 11:23:31 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-05-09 21:46:38 -0400
commit951c1fb03d80094c8b0d9bcc463d86fa71695b3a (patch)
tree28a03e1ad9256c5038a0351c806910e9b7ef5aef /libraries/ghc-prim
parentea86360f21e8c9812acba8dc1bc2a54fef700ece (diff)
downloadhaskell-951c1fb03d80094c8b0d9bcc463d86fa71695b3a.tar.gz
Fix unboxed-sums GC ptr-slot rubbish value (#17791)
This patch allows boot libraries to use unboxed sums without implicitly depending on `base` package because of `absentSumFieldError`. See updated Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make
Diffstat (limited to 'libraries/ghc-prim')
-rw-r--r--libraries/ghc-prim/GHC/Prim/Panic.hs45
-rw-r--r--libraries/ghc-prim/ghc-prim.cabal1
2 files changed, 46 insertions, 0 deletions
diff --git a/libraries/ghc-prim/GHC/Prim/Panic.hs b/libraries/ghc-prim/GHC/Prim/Panic.hs
new file mode 100644
index 0000000000..8dd8f03530
--- /dev/null
+++ b/libraries/ghc-prim/GHC/Prim/Panic.hs
@@ -0,0 +1,45 @@
+{-# LANGUAGE GHCForeignImportPrim #-}
+{-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE UnboxedTuples #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE EmptyCase #-}
+
+-- | Primitive panics.
+module GHC.Prim.Panic
+ ( absentSumFieldError
+ , panicError
+ )
+where
+
+import GHC.Prim
+import GHC.Magic
+
+default () -- Double and Integer aren't available yet
+
+-- `stg_panic#` never returns but it can't just return `State# RealWorld` so we
+-- indicate that it returns `Void#` too to make the compiler happy.
+foreign import prim "stg_paniczh" panic# :: Addr# -> State# RealWorld -> (# State# RealWorld, Void# #)
+
+-- | Display the CString whose address is given as an argument and exit.
+panicError :: Addr# -> a
+panicError errmsg =
+ runRW# (\s ->
+ case panic# errmsg s of
+ (# _, _ #) -> -- This bottom is unreachable but we can't
+ -- use an empty case lest the pattern match
+ -- checker squawks.
+ let x = x in x)
+
+-- | Closure introduced by GHC.Stg.Unarise for unused unboxed sum fields.
+--
+-- See Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make
+absentSumFieldError :: a
+absentSumFieldError = panicError "entered absent sum field!"#
+
+-- GHC.Core.Make.aBSENT_SUM_FIELD_ERROR_ID gives absentSumFieldError a bottoming
+-- demand signature. But if we ever inlined it (to a call to panicError) we'd
+-- lose that information. Should not happen because absentSumFieldError is only
+-- introduced in Stg.Unarise, long after inlining has stopped, but it seems
+-- more direct simply to give it a NOINLINE pragma
+{-# NOINLINE absentSumFieldError #-}
diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal
index 040eb43b27..607f24df99 100644
--- a/libraries/ghc-prim/ghc-prim.cabal
+++ b/libraries/ghc-prim/ghc-prim.cabal
@@ -46,6 +46,7 @@ Library
GHC.IntWord64
GHC.Magic
GHC.Prim.Ext
+ GHC.Prim.Panic
GHC.PrimopWrappers
GHC.Tuple
GHC.Types