Remove NOINLINE strictness hack
authorsimonpj@microsoft.com <unknown>
Mon, 8 May 2006 14:28:34 +0000 (14:28 +0000)
committersimonpj@microsoft.com <unknown>
Mon, 8 May 2006 14:28:34 +0000 (14:28 +0000)
The stricteness analyser used to have a HACK which ensured that NOINLNE things
were not strictness-analysed.  The reason was unsafePerformIO. Left to itself,
the strictness analyser would discover this strictness for unsafePerformIO:
unsafePerformIO:  C(U(AV))
But then consider this sub-expression
unsafePerformIO (\s -> let r = f x in
       case writeIORef v r s of (# s1, _ #) ->
       (# s1, r #)
The strictness analyser will now find that r is sure to be eval'd,
and may then hoist it out.  This makes tests/lib/should_run/memo002
deadlock.

Solving this by making all NOINLINE things have no strictness info is overkill.
In particular, it's overkill for runST, which is perfectly respectable.
Consider
f x = runST (return x)
This should be strict in x.

So the new plan is to define unsafePerformIO using the 'lazy' combinator:

unsafePerformIO (IO m) = lazy (case m realWorld# of (# _, r #) -> r)

Remember, 'lazy' is a wired-in identity-function Id, of type a->a, which is
magically NON-STRICT, and is inlined after strictness analysis.  So
unsafePerformIO will look non-strict, and that's what we want.

Now we don't need the hack in the strictness analyser.

compiler/basicTypes/MkId.lhs
compiler/stranal/DmdAnal.lhs
compiler/stranal/WorkWrap.lhs

index 84b3546..09540cc 100644 (file)
@@ -902,22 +902,26 @@ seqId
     ty  = mkForAllTys [alphaTyVar,openBetaTyVar]
                      (mkFunTy alphaTy (mkFunTy openBetaTy openBetaTy))
     [x,y] = mkTemplateLocals [alphaTy, openBetaTy]
--- gaw 2004
     rhs = mkLams [alphaTyVar,openBetaTyVar,x,y] (Case (Var x) x openBetaTy [(DEFAULT, [], Var y)])
 
 -- lazy :: forall a?. a? -> a?  (i.e. works for unboxed types too)
 -- Used to lazify pseq:                pseq a b = a `seq` lazy b
--- No unfolding: it gets "inlined" by the worker/wrapper pass
--- Also, no strictness: by being a built-in Id, it overrides all
--- the info in PrelBase.hi.  This is important, because the strictness
+-- 
+-- Also, no strictness: by being a built-in Id, all the info about lazyId comes from here,
+-- not from GHC.Base.hi.   This is important, because the strictness
 -- analyser will spot it as strict!
+--
+-- Also no unfolding in lazyId: it gets "inlined" by a HACK in the worker/wrapper pass
+--     (see WorkWrap.wwExpr)   
+-- We could use inline phases to do this, but that would be vulnerable to changes in 
+-- phase numbering....we must inline precisely after strictness analysis.
 lazyId
   = pcMiscPrelId lazyIdName ty info
   where
     info = noCafIdInfo
     ty  = mkForAllTys [alphaTyVar] (mkFunTy alphaTy alphaTy)
 
-lazyIdUnfolding :: CoreExpr    -- Used to expand LazyOp after strictness anal
+lazyIdUnfolding :: CoreExpr    -- Used to expand 'lazyId' after strictness anal
 lazyIdUnfolding = mkLams [openAlphaTyVar,x] (Var x)
                where
                  [x] = mkTemplateLocals [openAlphaTy]
index c5cfb7b..127fa78 100644 (file)
@@ -530,34 +530,6 @@ by dmdAnalTopBind.
 
 \begin{code}
 mk_sig_ty never_inline thunk_cpr_ok rhs (DmdType fv dmds res) 
-  | never_inline && not (isBotRes res)
-       --                      HACK ALERT
-       -- Don't strictness-analyse NOINLINE things.  Why not?  Because
-       -- the NOINLINE says "don't expose any of the inner workings at the call 
-       -- site" and the strictness is certainly an inner working.
-       --
-       -- More concretely, the demand analyser discovers the following strictness
-       -- for unsafePerformIO:  C(U(AV))
-       -- But then consider
-       --      unsafePerformIO (\s -> let r = f x in 
-       --                             case writeIORef v r s of (# s1, _ #) ->
-       --                             (# s1, r #)
-       -- The strictness analyser will find that the binding for r is strict,
-       -- (becuase of uPIO's strictness sig), and so it'll evaluate it before 
-       -- doing the writeIORef.  This actually makes tests/lib/should_run/memo002
-       -- get a deadlock!  
-       --
-       -- Solution: don't expose the strictness of unsafePerformIO.
-       --
-       -- But we do want to expose the strictness of error functions, 
-       -- which are also often marked NOINLINE
-       --      {-# NOINLINE foo #-}
-       --      foo x = error ("wubble buggle" ++ x)
-       -- So (hack, hack) we only drop the strictness for non-bottom things
-       -- This is all very unsatisfactory.
-  = (deferEnv fv, topSig)
-
-  | otherwise
   = (lazy_fv, mkStrictSig dmd_ty)
   where
     dmd_ty = DmdType strict_fv final_dmds res'
index 64eba89..d964026 100644 (file)
@@ -137,7 +137,7 @@ wwExpr e@(Note InlineMe expr) = returnUs e
 wwExpr e@(Var v)
   | v `hasKey` lazyIdKey = returnUs lazyIdUnfolding
   | otherwise            = returnUs e
-       -- Inline 'lazy' after strictness analysis
+       -- HACK alert: Inline 'lazy' after strictness analysis
        -- (but not inside InlineMe's)
 
 wwExpr (Lam binder expr)