summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2020-04-24 17:22:44 -0400
committerBen Gamari <ben@smart-cactus.org>2020-05-22 23:28:03 -0400
commit3ddb90189212c5a5282cd9a0581cf288539206a4 (patch)
tree541f76d7a23544d959da9404421c73644a403216
parent566cc73f46d67e2b36fda95d0253067bb0ecc12f (diff)
downloadhaskell-wip/T18079.tar.gz
Eta expand un-saturated primopswip/T18079
Now since we no longer try to predict CAFfyness we have no need for the solution to #16846. Eta expanding unsaturated primop applications is conceptually simpler, especially in the presence of levity polymorphism. This essentially reverts cac8dc9f51e31e4c0a6cd9bc302f7e1bc7c03beb, as suggested in #18079. Closes #18079.
-rw-r--r--compiler/GHC/Builtin/PrimOps.hs92
-rw-r--r--compiler/GHC/ByteCode/Linker.hs1
-rw-r--r--compiler/GHC/CoreToStg.hs12
-rw-r--r--compiler/GHC/CoreToStg/Prep.hs12
-rw-r--r--compiler/GHC/Types/Id.hs18
-rw-r--r--testsuite/tests/codeGen/should_fail/T13233.hs3
-rw-r--r--testsuite/tests/codeGen/should_fail/T13233.stderr12
-rw-r--r--testsuite/tests/codeGen/should_fail/T13233_elab.stderr9
8 files changed, 108 insertions, 51 deletions
diff --git a/compiler/GHC/Builtin/PrimOps.hs b/compiler/GHC/Builtin/PrimOps.hs
index 8ad0b731f8..96d5a5ad0d 100644
--- a/compiler/GHC/Builtin/PrimOps.hs
+++ b/compiler/GHC/Builtin/PrimOps.hs
@@ -590,33 +590,85 @@ primOpOcc op = case primOpInfo op of
{- Note [Primop wrappers]
~~~~~~~~~~~~~~~~~~~~~~~~~
-Previously hasNoBinding would claim that PrimOpIds didn't have a curried
-function definition. This caused quite some trouble as we would be forced to
-eta expand unsaturated primop applications very late in the Core pipeline. Not
-only would this produce unnecessary thunks, but it would also result in nasty
-inconsistencies in CAFfy-ness determinations (see #16846 and
-Note [CAFfyness inconsistencies due to late eta expansion] in GHC.Iface.Tidy).
-
-However, it was quite unnecessary for hasNoBinding to claim this; primops in
-fact *do* have curried definitions which are found in GHC.PrimopWrappers, which
-is auto-generated by utils/genprimops from prelude/primops.txt.pp. These wrappers
-are standard Haskell functions mirroring the types of the primops they wrap.
-For instance, in the case of plusInt# we would have:
+
+To support (limited) use of primops in GHCi genprimopcode generates the
+GHC.PrimopWrappers module. This module contains a "primop wrapper"
+binding for each primop. These are standard Haskell functions mirroring the
+types of the primops they wrap. For instance, in the case of plusInt# we would
+have:
module GHC.PrimopWrappers where
import GHC.Prim as P
+
+ plusInt# :: Int# -> Int# -> Int#
plusInt# a b = P.plusInt# a b
-We now take advantage of these curried definitions by letting hasNoBinding
-claim that PrimOpIds have a curried definition and then rewrite any unsaturated
-PrimOpId applications that we find during CoreToStg as applications of the
-associated wrapper (e.g. `GHC.Prim.plusInt# 3#` will get rewritten to
-`GHC.PrimopWrappers.plusInt# 3#`).` The Id of the wrapper for a primop can be
-found using 'PrimOp.primOpWrapperId'.
+The Id for the wrapper of a primop can be found using
+'GHC.Builtin.PrimOp.primOpWrapperId'. However, GHCi does not use this mechanism
+to link primops; it rather does a rather hacky symbol lookup (see
+GHC.ByteCode.Linker.primopToCLabel). TODO: Perhaps this should be changed?
+
+Note that these wrappers aren't *quite*
+as expressive as their unwrapped breathern in that they may exhibit less levity
+polymorphism. For instance, consider the case of mkWeakNoFinalizer# which has
+type:
+
+ mkWeakNoFinalizer# :: forall (r :: RuntimeRep) (k :: TYPE r) (v :: Type).
+ k -> v
+ -> State# RealWorld
+ -> (# State# RealWorld, Weak# v #)
+
+Naively we could generate a wrapper of the form,
+
+
+ mkWeakNoFinalizer# k v s = GHC.Prim.mkWeakNoFinalizer# k v s
+
+However, this would require that 'k' bind the levity-polymorphic key,
+which is disallowed by our levity polymorphism validity checks (see Note
+[Levity polymorphism invariants] in GHC.Core). Consequently, we give the
+wrapper the simpler, less polymorphic type
+
+ mkWeakNoFinalizer# :: forall (k :: Type) (v :: Type).
+ k -> v
+ -> State# RealWorld
+ -> (# State# RealWorld, Weak# v #)
+
+This simplification tends to be good enough for GHCi uses given that there are
+few levity polymorphic primops and we do little simplification on interpreted
+code anyways.
+
+TODO: This behavior is actually wrong; a program becomes ill-typed upon
+replacing a real primop occurrence with one of its wrapper due to the fact that
+the former has an additional type binder. Hmmm....
+
+Note [Eta expanding primops]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+STG requires that primop applications be saturated. This makes code generation
+significantly simpler since otherwise we would need to define a calling
+convention for curried applications that can accomodate levity polymorphism.
+
+To ensure saturation, CorePrep eta expands expand all primop applications as
+described in Note [Eta expansion of hasNoBinding things in CorePrep] in
+GHC.Core.Prep.
+
+Historical Note:
+
+For a short period around GHC 8.8 we rewrote unsaturated primop applications to
+rather use the primop's wrapper (see Note [Primop wrappers] in
+GHC.Builtin.PrimOps) instead of eta expansion. This was because at the time
+CoreTidy would try to predict the CAFfyness of bindings that would be produced
+by CorePrep for inclusion in interface files. Eta expanding during CorePrep
+proved to be very difficult to predict, leading to nasty inconsistencies in
+CAFfyness determinations (see #16846).
-Nota Bene: GHC.PrimopWrappers is needed *regardless*, because it's
-used by GHCi, which does not implement primops direct at all.
+Thankfully, we now no longer try to predict CAFfyness but rather compute it on
+GHC STG (see Note [SRTs] in GHC.Cmm.Info.Build) and inject it into the interface
+file after code generation (see TODO: Refer to whatever falls out of #18096).
+This is much simpler and avoids the potential for inconsistency, allowing us to
+return to the somewhat simpler eta expansion approach for unsaturated primops.
+See #18079.
-}
-- | Returns the 'Id' of the wrapper associated with the given 'PrimOp'.
diff --git a/compiler/GHC/ByteCode/Linker.hs b/compiler/GHC/ByteCode/Linker.hs
index bda0e03445..1fab779619 100644
--- a/compiler/GHC/ByteCode/Linker.hs
+++ b/compiler/GHC/ByteCode/Linker.hs
@@ -176,6 +176,7 @@ nameToCLabel n suffix = mkFastString label
]
+-- See Note [Primop wrappers] in GHC.Builtin.PrimOps
primopToCLabel :: PrimOp -> String -> String
primopToCLabel primop suffix = concat
[ "ghczmprim_GHCziPrimopWrappers_"
diff --git a/compiler/GHC/CoreToStg.hs b/compiler/GHC/CoreToStg.hs
index 24e21b1901..0dfe5ab240 100644
--- a/compiler/GHC/CoreToStg.hs
+++ b/compiler/GHC/CoreToStg.hs
@@ -45,7 +45,7 @@ import GHC.Driver.Session
import GHC.Driver.Ways
import GHC.Types.ForeignCall
import GHC.Types.Demand ( isUsedOnce )
-import GHC.Builtin.PrimOps ( PrimCall(..), primOpWrapperId )
+import GHC.Builtin.PrimOps ( PrimCall(..) )
import GHC.Types.SrcLoc ( mkGeneralSrcSpan )
import GHC.Builtin.Names ( unsafeEqualityProofName )
@@ -539,12 +539,10 @@ coreToStgApp f args ticks = do
(dropRuntimeRepArgs (fromMaybe [] (tyConAppArgs_maybe res_ty)))
-- Some primitive operator that might be implemented as a library call.
- -- As described in Note [Primop wrappers] in GHC.Builtin.PrimOps, here we
- -- turn unsaturated primop applications into applications of
- -- the primop's wrapper.
- PrimOpId op
- | saturated -> StgOpApp (StgPrimOp op) args' res_ty
- | otherwise -> StgApp (primOpWrapperId op) args'
+ -- As noted by Note [Eta expanding primops] in GHC.Builtin.PrimOps
+ -- we require that primop applications be saturated.
+ PrimOpId op -> ASSERT( saturated )
+ StgOpApp (StgPrimOp op) args' res_ty
-- A call to some primitive Cmm function.
FCallId (CCall (CCallSpec (StaticTarget _ lbl (Just pkgId) True)
diff --git a/compiler/GHC/CoreToStg/Prep.hs b/compiler/GHC/CoreToStg/Prep.hs
index 8d4750c9e4..102f10de4f 100644
--- a/compiler/GHC/CoreToStg/Prep.hs
+++ b/compiler/GHC/CoreToStg/Prep.hs
@@ -71,7 +71,7 @@ import qualified Data.Set as S
The goal of this pass is to prepare for code generation.
-1. Saturate constructor applications.
+1. Saturate constructor and primop applications.
2. Convert to A-normal form; that is, function arguments
are always variables.
@@ -1067,15 +1067,11 @@ maybeSaturate deals with eta expanding to saturate things that can't deal with
unsaturated applications (identified by 'hasNoBinding', currently just
foreign calls and unboxed tuple/sum constructors).
-Note that eta expansion in CorePrep is very fragile due to the "prediction" of
-CAFfyness made during tidying (see Note [CAFfyness inconsistencies due to eta
-expansion in CorePrep] in GHC.Iface.Tidy for details. We previously saturated primop
+Historical Note: Note that eta expansion in CorePrep used to be very fragile
+due to the "prediction" of CAFfyness that we used to make during tidying.
+We previously saturated primop
applications here as well but due to this fragility (see #16846) we now deal
with this another way, as described in Note [Primop wrappers] in GHC.Builtin.PrimOps.
-
-It's quite likely that eta expansion of constructor applications will
-eventually break in a similar way to how primops did. We really should
-eliminate this case as well.
-}
maybeSaturate :: Id -> CpeApp -> Int -> UniqSM CpeRhs
diff --git a/compiler/GHC/Types/Id.hs b/compiler/GHC/Types/Id.hs
index 3d9d9c3f40..eaa97f6900 100644
--- a/compiler/GHC/Types/Id.hs
+++ b/compiler/GHC/Types/Id.hs
@@ -515,20 +515,12 @@ hasNoBinding :: Id -> Bool
-- ^ Returns @True@ of an 'Id' which may not have a
-- binding, even though it is defined in this module.
--- Data constructor workers used to be things of this kind, but
--- they aren't any more. Instead, we inject a binding for
--- them at the CorePrep stage.
---
--- 'PrimOpId's also used to be of this kind. See Note [Primop wrappers] in GHC.Builtin.PrimOps.
--- for the history of this.
---
--- Note that CorePrep currently eta expands things no-binding things and this
--- can cause quite subtle bugs. See Note [Eta expansion of hasNoBinding things
--- in CorePrep] in CorePrep for details.
---
--- EXCEPT: unboxed tuples, which definitely have no binding
+-- Data constructor workers used to be things of this kind, but they aren't any
+-- more. Instead, we inject a binding for them at the CorePrep stage. The
+-- exception to this is unboxed tuples and sums datacons, which definitely have
+-- no binding
hasNoBinding id = case Var.idDetails id of
- PrimOpId _ -> False -- See Note [Primop wrappers] in GHC.Builtin.PrimOps
+ PrimOpId _ -> True -- See Note [Eta expanding primops] in GHC.Builtin.PrimOps
FCallId _ -> True
DataConWorkId dc -> isUnboxedTupleCon dc || isUnboxedSumCon dc
_ -> isCompulsoryUnfolding (idUnfolding id)
diff --git a/testsuite/tests/codeGen/should_fail/T13233.hs b/testsuite/tests/codeGen/should_fail/T13233.hs
index 82e08e207b..f24fc03bfb 100644
--- a/testsuite/tests/codeGen/should_fail/T13233.hs
+++ b/testsuite/tests/codeGen/should_fail/T13233.hs
@@ -21,9 +21,6 @@ obscure _ = ()
quux :: ()
quux = obscure (#,#)
--- It used to be that primops has no binding. However, as described in
--- Note [Primop wrappers] in GHC.Builtin.PrimOps we now rewrite unsaturated primop
--- applications to their wrapper, which allows safe use of levity polymorphism.
primop :: forall (rep :: RuntimeRep) (a :: TYPE rep) b c.
a -> b -> (State# RealWorld -> (# State# RealWorld, c #))
-> State# RealWorld -> (# State# RealWorld, Weak# b #)
diff --git a/testsuite/tests/codeGen/should_fail/T13233.stderr b/testsuite/tests/codeGen/should_fail/T13233.stderr
index a3d77d0b73..f6254778c1 100644
--- a/testsuite/tests/codeGen/should_fail/T13233.stderr
+++ b/testsuite/tests/codeGen/should_fail/T13233.stderr
@@ -20,3 +20,15 @@ T13233.hs:22:16: error:
Levity-polymorphic arguments:
a :: TYPE rep1
b :: TYPE rep2
+
+T13233.hs:27:10: error:
+ Cannot use function with levity-polymorphic arguments:
+ mkWeak# :: a
+ -> b
+ -> (State# RealWorld -> (# State# RealWorld, c #))
+ -> State# RealWorld
+ -> (# State# RealWorld, Weak# b #)
+ (Note that levity-polymorphic primops such as 'coerce' and unboxed tuples
+ are eta-expanded internally because they must occur fully saturated.
+ Use -fprint-typechecker-elaboration to display the full expression.)
+ Levity-polymorphic arguments: a :: TYPE rep
diff --git a/testsuite/tests/codeGen/should_fail/T13233_elab.stderr b/testsuite/tests/codeGen/should_fail/T13233_elab.stderr
index 214e982222..40a12ecd62 100644
--- a/testsuite/tests/codeGen/should_fail/T13233_elab.stderr
+++ b/testsuite/tests/codeGen/should_fail/T13233_elab.stderr
@@ -18,3 +18,12 @@ T13233_elab.hs:25:16: error:
Levity-polymorphic arguments:
a :: TYPE rep1
b :: TYPE rep2
+
+T13233_elab.hs:33:10:
+ Cannot use function with levity-polymorphic arguments:
+ mkWeak# @rep @a @b @c :: a
+ -> b
+ -> (State# RealWorld -> (# State# RealWorld, c #))
+ -> State# RealWorld
+ -> (# State# RealWorld, Weak# b #)
+ Levity-polymorphic arguments: a :: TYPE rep