[Git][ghc/ghc][wip/runRW] 5 commits: CoreLint: Again accept casts

Ben Gamari gitlab at gitlab.haskell.org
Fri Apr 24 01:43:47 UTC 2020



Ben Gamari pushed to branch wip/runRW at Glasgow Haskell Compiler / GHC


Commits:
7d1b4767 by Ben Gamari at 2020-04-21T21:27:03+00:00
CoreLint: Again accept casts

- - - - -
179d0bbe by Simon Peyton Jones at 2020-04-21T23:17:48+00:00
Make Lint check return type of a join point

Consider
   join x = rhs in body
It's important that the type of 'rhs' is the same as the type of
'body', but Lint wasn't checking that invariant.

Now it does!  This was exposed by investigation into !3113.

- - - - -
54fc0e73 by Simon Peyton Jones at 2020-04-21T23:17:49+00:00
Do not float join points in exprIsConApp_maybe

We hvae been making exprIsConApp_maybe cleverer in recent times:

    commit b78cc64e923716ac0512c299f42d4d0012306c05
    Date:   Thu Nov 15 17:14:31 2018 +0100
    Make constructor wrappers inline only during the final phase

    commit 7833cf407d1f608bebb1d38bb99d3035d8d735e6
    Date:   Thu Jan 24 17:58:50 2019 +0100
    Look through newtype wrappers (Trac #16254)

    commit c25b135ff5b9c69a90df0ccf51b04952c2dc6ee1
    Date:   Thu Feb 21 12:03:22 2019 +0000
    Fix exprIsConApp_maybe

But alas there was still a bug, now immortalised in
  Note [Don't float join points]
in SimpleOpt.

It's quite hard to trigger because it requires a dead
join point, but it came up when compiling Cabal
Cabal.Distribution.Fields.Lexer.hs, when working on
!3113.

Happily, the fix is extremly easy.  Finding the
bug was not so easy.

- - - - -
be9bb0d7 by Ben Gamari at 2020-04-23T13:48:34+00:00
Merge commit 'fad536ea7e2622fb1102df55bd642b4153603503' into HEAD

- - - - -
6965215a by Ben Gamari at 2020-04-24T00:46:31+00:00
CoreLint: Accept oversaturated applications of runRW#

- - - - -


1 changed file:

- compiler/GHC/Core/Lint.hs


Changes:

=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -780,10 +780,9 @@ type LintedId       = Id
 
 -- | Lint an expression cast through the given coercion, returning the type
 -- resulting from the cast.
-lintCastExpr :: CoreExpr -> Coercion -> LintM LintedType
-lintCastExpr expr co
-  = do { expr_ty <- markAllJoinsBad $ lintCoreExpr expr
-       ; co' <- lintCoercion co
+lintCastExpr :: CoreExpr -> LintedType -> Coercion -> LintM LintedType
+lintCastExpr expr expr_ty co
+  = do { co' <- lintCoercion co
        ; let (Pair from_ty to_ty, role) = coercionKindRole co'
        ; checkValueType to_ty $
          text "target of cast" <+> quotes (ppr co')
@@ -808,7 +807,8 @@ lintCoreExpr (Lit lit)
   = return (literalType lit)
 
 lintCoreExpr (Cast expr co)
-  = markAllJoinsBad $ lintCastExpr expr co
+  = do expr_ty <- markAllJoinsBad   $ lintCoreExpr expr
+       lintCastExpr expr expr_ty co
 
 lintCoreExpr (Tick tickish expr)
   = do case tickish of
@@ -870,11 +870,22 @@ lintCoreExpr e@(Let (Rec pairs) body)
 lintCoreExpr e@(App _ _)
   | Var fun <- fun
   , fun `hasKey` runRWKey
-  , [arg_ty1, arg_ty2, arg3] <- args
+    -- N.B. we may have an over-saturated application of the form:
+    --   runRW (\s -> \x -> ...) y
+  , arg_ty1 : arg_ty2 : arg3 : rest <- args
   = do { fun_ty1 <- lintCoreArg (idType fun) arg_ty1
        ; fun_ty2 <- lintCoreArg fun_ty1      arg_ty2
-       ; arg3_ty <- lintJoinLams 1 (Just fun) arg3
-       ; lintValApp arg3 fun_ty2 arg3_ty }
+         -- The simplifier pushes casts out of the continuation lambda;
+         -- consequently we need to handle the case that the continuation is a
+         -- cast lambda. See Note [Casts and lambdas] in
+         -- GHC.Core.Opt.Simplify.Utils.
+       ; arg3_ty <- case arg3 of
+                      Cast expr co -> do
+                        expr_ty <- lintJoinLams 1 (Just fun) expr
+                        lintCastExpr expr expr_ty co
+                      _ -> lintJoinLams 1 (Just fun) arg3
+       ; app_ty <- lintValApp arg3 fun_ty2 arg3_ty
+       ; lintCoreArgs app_ty rest }
 
   | Var fun <- fun
   , fun `hasKey` runRWKey



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fad536ea7e2622fb1102df55bd642b4153603503...6965215a5b3b4982af4321a2714d11756a688325

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fad536ea7e2622fb1102df55bd642b4153603503...6965215a5b3b4982af4321a2714d11756a688325
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200423/d3f1a518/attachment-0001.html>


More information about the ghc-commits mailing list