<div dir="ltr">Unfortunately, now that I had the opportunity to try to validate my change, it turns out it is *not* working, since it breaks deSugar/should_run/dsrun014.<div><br></div><div>My code is pushed to the wip/desugar-unfold branch, but all it does is change dsExpr from</div><div><div><br></div><div>dsExpr (HsVar var) = return (varToCoreExpr var)   -- See Note [Desugaring vars]</div><div><br></div></div><div>to</div><div><br></div><div><div>dsExpr (HsVar var)            -- See Note [Unfolding while desugaring]</div><div>  | isCompulsoryUnfolding unfolding = return $ unfoldingTemplate unfolding</div><div>  | otherwise = return (varToCoreExpr var)   -- See Note [Desugaring vars]</div><div>  where</div><div>    unfolding = idUnfolding var</div></div><div><br></div><div><br></div><div>The important bit of the test in question is:</div><div><br></div><div><div>{-# NOINLINE f #-}</div><div>f :: a -> b -> (# a,b #)</div><div>f x y = x `seq` y `seq` (# x,y #)</div></div><div><br></div><div><br></div><div><br></div><div>Here's what it is desugared into with master:</div><div><br></div><div><div>f [InlPrag=NOINLINE]</div><div>  :: forall a_avA b_avB. a_avA -> b_avB -> (# a_avA, b_avB #)</div><div>[LclIdX, Str=DmdType]</div><div>f =</div><div>  \ (@ a_aAj) (@ b_aAk) -></div><div>    letrec {</div><div>      f_aAl :: a_aAj -> b_aAk -> (# a_aAj, b_aAk #)</div><div>      [LclId, Str=DmdType]</div><div>      f_aAl =</div><div>        \ (x_avC :: a_aAj) (y_avD :: b_aAk) -></div><div>          break<2>()</div><div>          break<1>(x_avC,y_avD)</div><div>          case x_avC of x_avC { __DEFAULT -></div><div>          break<0>(x_avC,y_avD)</div><div>          case y_avD of y_avD { __DEFAULT -> (# x_avC, y_avD #) }</div><div>          }; } in</div><div>    f_aAl</div></div><div><br></div><div><br></div><div><br></div><div>and here is the desugaring with the above change to dsExpr:</div><div><br></div><div><div>f [InlPrag=NOINLINE]</div><div>  :: forall a_avA b_avB. a_avA -> b_avB -> (# a_avA, b_avB #)</div><div>[LclIdX, Str=DmdType]</div><div>f =</div><div>  \ (@ a_aAj) (@ b_aAk) -></div><div>    letrec {</div><div>      f_aAl :: a_aAj -> b_aAk -> (# a_aAj, b_aAk #)</div><div>      [LclId, Str=DmdType]</div><div>      f_aAl =</div><div>        \ (x_avC :: a_aAj) (y_avD :: b_aAk) -></div><div>          break<2>()</div><div>          break<1>(x_avC,y_avD)</div><div>          case break<0>(x_avC,y_avD)</div><div>               (\ (@ a_12)</div><div>                  (@ b_13)</div><div>                  (tpl_B1 [Occ=Once] :: a_12)</div><div>                  (tpl_B2 [Occ=Once] :: b_13) -></div><div>                  case tpl_B1 of _ [Occ=Dead] { __DEFAULT -> tpl_B2 })</div><div>                 @ b_aAk @ (# a_aAj, b_aAk #) y_avD (# x_avC, y_avD #)</div><div>          of wild_00 { __DEFAULT -></div><div>          (\ (@ a_12)</div><div>             (@ b_13)</div><div>             (tpl_B1 [Occ=Once] :: a_12)</div><div>             (tpl_B2 [Occ=Once] :: b_13) -></div><div>             case tpl_B1 of _ [Occ=Dead] { __DEFAULT -> tpl_B2 })</div><div>            @ a_aAj @ (# a_aAj, b_aAk #) x_avC wild_00</div><div>          }; } in</div><div>    f_aAl</div></div><div><br></div><div><br></div><div>This trips up the core linter on the application of the inner lambda on the unboxed tuple type:</div><div><br></div><div><div>    In the expression: (\ (@ a_12)</div><div>                          (@ b_13)</div><div>                          (tpl_B1 [Occ=Once] :: a_12)</div><div>                          (tpl_B2 [Occ=Once] :: b_13) -></div><div>                          case tpl_B1 of _ [Occ=Dead] { __DEFAULT -> tpl_B2 })</div><div>                         @ b_aAk @ (# a_aAj, b_aAk #) y_avD (# x_avC, y_avD #)</div><div>    Kinds don't match in type application:</div><div>    Type variable: b_13 :: *</div><div>    Arg type: (# a_aAj, b_aAk #) :: #</div><div>    xx #</div></div><div><br></div><div>So.... yeah. Is there a more narrow predicate than isCompulsoryUnfolding that I should be checking for?</div><div><br></div><div>Bye,</div><div>    Gergo</div></div><div class="gmail_extra"><br><div class="gmail_quote">On Wed, Nov 12, 2014 at 10:23 AM, Dr. ÉRDI Gergő <span dir="ltr"><<a href="mailto:gergo@erdi.hu" target="_blank">gergo@erdi.hu</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><p dir="ltr">Yep, that seems to work. I'll add a note explaining why we need unfoldings here.</p><div class="HOEnZb"><div class="h5">
<div class="gmail_quote">On Nov 11, 2014 10:14 PM, "Simon Peyton Jones" <<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>> wrote:<br type="attribution"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Oh bother, that is _so_ tiresome. The desugarer establishes the let/app invariant, so we get<br>
<br>
        I# x_help<br>
<br>
but if x_help has a compulsory unfolding to (x void), returning an Int#, that violates the let/app invariant.  Sigh.  This is a ridiculous amount of work for a tiny corner (pattern synonyms for unboxed constants).<br>
<br>
Harump.  Let's see.  We are talking only of things like this<br>
<br>
        pattern P = 4#<br>
<br>
correct?  Perhaps it may be simpler to make the psWrapper in PatSyn be<br>
        psWrapper :: Either Id Literal<br>
and treat such patterns specially from the moment we first see them?  That would eliminate all this void stuff entirely.<br>
<br>
Pursuing the current line, though, I suppose that the desugarer could inline compulsory unfoldings during desugaring itself.  In this line, add a case for when var has a compulsory unfolding.<br>
<br>
dsExpr (HsVar var)            = return (varToCoreExpr var)   -- See Note [Desugaring vars]<br>
<br>
That would, I suppose, be the quickest pathc.<br>
<br>
Simon<br>
<br>
|  -----Original Message-----<br>
|  From: ghc-devs [mailto:<a href="mailto:ghc-devs-bounces@haskell.org" target="_blank">ghc-devs-bounces@haskell.org</a>] On Behalf Of Dr.<br>
|  ERDI Gergo<br>
|  Sent: 08 November 2014 14:03<br>
|  To: GHC Devs<br>
|  Subject: let/app invariant violated by code generated with mkCoreApp<br>
|<br>
|  Hi,<br>
|<br>
|  I'm trying to attach (f Void#) as a compulsory unfolding to an Id.<br>
|  Here's what I tried originally:<br>
|<br>
|       let unfolding = mkCoreApp (Var worker_id) (Var voidPrimId)<br>
|           wrapper_id' = setIdUnfolding wrapper_id $<br>
|  mkCompulsoryUnfolding unfolding<br>
|<br>
|  However, when I try to use wrapper_id' in the desugarer, the Core<br>
|  linter looks at me strange. This is the original Core:<br>
|<br>
|  f :: Int<br>
|  [LclIdX, Str=DmdType]<br>
|  f = break<1>() GHC.Types.I# Main.$WPAT<br>
|<br>
|  and this is the error message ($WPAT is the wrapper_id', PAT is the<br>
|  worker_id in this example)<br>
|<br>
|  <no location info>: Warning:<br>
|       In the expression: I# (PAT void#)<br>
|       This argument does not satisfy the let/app invariant: PAT void#<br>
|<br>
|  Now, I thought I'd make sure mkCoreApp generated correct Core by<br>
|  writing it out by hand:<br>
|<br>
|       let unfolding = Case (Var voidPrimId) voidArgId pat_ty<br>
|  [(DEFAULT,[],App (Var worker_id) (Var voidArgId))]<br>
|<br>
|  however, bizarrely, this *still* results in *the same* error message,<br>
|  as if something was transforming it back to a straight App.<br>
|<br>
|  Anyone have any hints what I'm doing wrong here?<br>
|<br>
|  Bye,<br>
|       Gergo<br>
|<br>
|  --<br>
|<br>
|     .--= ULLA! =-----------------.<br>
|      \     <a href="http://gergo.erdi.hu" target="_blank">http://gergo.erdi.hu</a>   \<br>
|       `---= <a href="mailto:gergo@erdi.hu" target="_blank">gergo@erdi.hu</a> =-------'<br>
|  You are in a twisty maze of little install diskettes.<br>
|  _______________________________________________<br>
|  ghc-devs mailing list<br>
|  <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
|  <a href="http://www.haskell.org/mailman/listinfo/ghc-devs" target="_blank">http://www.haskell.org/mailman/listinfo/ghc-devs</a><br>
</blockquote></div>
</div></div></blockquote></div><br></div>