<div dir="ltr"><div><div>Ok, I am making progress, when it is done I will put up a patch.<br><br></div>I figured I was probably posting too much, sorry all.<br><br></div>Alan<br></div><div class="gmail_extra"><br><div class="gmail_quote">On Fri, Apr 10, 2015 at 2:08 PM, Simon Peyton Jones <span dir="ltr"><<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">





<div link="blue" vlink="purple" lang="EN-GB">
<div>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">You are describing code I cannot see.  Can you perhaps just work out what is happening and fix it?  Nothing very deep is here, I think.  If you get really stuck and
 cannot make progress then put it in a Phab patch and I will try to look.  But I’m struggling with time at the moment.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Simon<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"><u></u> <u></u></span></p>
<div style="border:none;border-left:solid blue 1.5pt;padding:0cm 0cm 0cm 4.0pt">
<div>
<div style="border:none;border-top:solid #e1e1e1 1.0pt;padding:3.0pt 0cm 0cm 0cm">
<p class="MsoNormal"><b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US">From:</span></b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US"> Alan & Kim Zimmerman [mailto:<a href="mailto:alan.zimm@gmail.com" target="_blank">alan.zimm@gmail.com</a>]
<br>
<b>Sent:</b> 10 April 2015 13:05</span></p><div><div class="h5"><br>
<b>To:</b> Simon Peyton Jones<br>
<b>Cc:</b> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
<b>Subject:</b> Re: Collapsing HsForAllTy, again<u></u><u></u></div></div><p></p>
</div>
</div><div><div class="h5">
<p class="MsoNormal"><u></u> <u></u></p>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
And once the splitLHsForAllTy is sorted, this<br>
<br>
tc_inst_head :: HsType Name -> TcM TcType<br>
tc_inst_head (HsForAllTy _ _ hs_tvs hs_ctxt hs_ty)<br>
  = tcHsTyVarBndrs hs_tvs $ \ tvs -><br>
    do { ctxt <- tcHsContext hs_ctxt<br>
       ; ty   <- tc_lhs_type hs_ty ekConstraint    -- Body for forall has kind Constraint<br>
       ; return (mkSigmaTy tvs ctxt ty) }<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
results in<br>
<br>
libraries/base/Data/Monoid.hs:217:23:<br>
    Illegal constraint: Alternative f => Monoid (Alt f a)<br>
    In the instance declaration for ‘Alternative f => Monoid (Alt f a)’<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
Alan<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
<u></u> <u></u></p>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
On Fri, Apr 10, 2015 at 1:11 PM, Alan & Kim Zimmerman <<a href="mailto:alan.zimm@gmail.com" target="_blank">alan.zimm@gmail.com</a>> wrote:<u></u><u></u></p>
<blockquote style="border:none;border-left:solid #cccccc 1.0pt;padding:0cm 0cm 0cm 6.0pt;margin-left:4.8pt;margin-right:0cm">
<div>
<div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
It looks like<br>
<br>
splitLHsForAllTy<br>
    :: LHsType name<br>
    -> (LHsTyVarBndrs name, HsContext name, LHsType name)<br>
splitLHsForAllTy poly_ty<br>
  = case unLoc poly_ty of<br>
        HsParTy ty                -> splitLHsForAllTy ty<br>
        HsForAllTy _ _ tvs cxt ty -> (tvs, unLoc cxt, ty)<br>
        _                         -> (emptyHsQTvs, [], poly_ty)<br>
        -- The type vars should have been computed by now, even if they were implicit<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
needs a recursive call for the HsForAllTy case, it now generates<br>
<br>
libraries/base/Data/Monoid.hs:217:10:<br>
    Malformed instance: forall f a. Alternative f => Monoid (Alt f a)<span style="color:#888888"><br>
<br>
</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
<span><span style="color:#888888">Alan</span></span><u></u><u></u></p>
</div>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
<u></u> <u></u></p>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:6.0pt;margin-left:0cm">
On Fri, Apr 10, 2015 at 10:13 AM, Simon Peyton Jones <<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>> wrote:<u></u><u></u></p>
<blockquote style="border:none;border-left:solid #cccccc 1.0pt;padding:0cm 0cm 0cm 6.0pt;margin-left:4.8pt;margin-right:0cm">
<div>
<div>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Look at how instance declarations are parsed. If you look at Parser.y you’ll see that for</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p>instance (Eq a, Eq b) => Eq (a,b)<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">we get (in effect)</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p>mkImplicitHsForAllTy (mkQualifiedHsForAllTy (Eq a, Eq b) (Eq (a,b))<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">The outer mkImplicit.. is to ensure that there is always, in the end, a HsForAllTy around the whole thing, even around
</span><u></u><u></u></p>
<p>instance Eq a<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">say.</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">But we don’t actually want two nested HsForAllTys.  mk_forall_ty collapsed the two. 
</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">But you don’t want that either.  So I think you should make mkImplictHsForAllTy do the test instead.  Its goal is to wrap a HsForallTy
 if there isn’t one already. So</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p>mkImplicitHsForAllTy (HsForAllTy exp tvs cxt ty)<u></u><u></u></p>
<p>  = HsForAllTy exp’ tvs cxt ty<u></u><u></u></p>
<p>  where<u></u><u></u></p>
<p>    exp’ = case exp of<u></u><u></u></p>
<p>             Qualified -> Implicit<u></u><u></u></p>
<p>             _         -> exp<u></u><u></u></p>
<p>mkImplicitHsForAllTy ty = mkHsForAllTy Implicit  []  (L loc _) ty<u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">should do the job.</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Incidentally, mkImplicitHsForAllTy should not take a ctxt argument.  If you have a non-empty context, use mkQualifiedHsForAllTy. 
 That means that in Convert you’ll need to use</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">   mkHsForAllTy Implicit ctxt ty’</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">instead of mkImplicitHsForAllTy</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif">Simon</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif"> </span><u></u><u></u></p>
<div style="border:none;border-left:solid blue 1.5pt;padding:0cm 0cm 0cm 4.0pt">
<div>
<div style="border:none;border-top:solid #e1e1e1 1.0pt;padding:3.0pt 0cm 0cm 0cm">
<p class="MsoNormal"><b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US">From:</span></b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US"> Alan
 & Kim Zimmerman [mailto:<a href="mailto:alan.zimm@gmail.com" target="_blank">alan.zimm@gmail.com</a>]
<br>
<b>Sent:</b> 10 April 2015 08:02<br>
<b>To:</b> Simon Peyton Jones<br>
<b>Cc:</b> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
<b>Subject:</b> Re: Collapsing HsForAllTy, again</span><u></u><u></u></p>
</div>
</div>
<div>
<div>
<p class="MsoNormal"> <u></u><u></u></p>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt">If I replace it with<br>
<br>
<br>
mkHsForAllTy :: HsExplicitFlag -> [LHsTyVarBndr RdrName] -> LHsContext RdrName -> LHsType RdrName -> HsType RdrName<br>
-- Smart constructor for HsForAllTy<br>
-- mkHsForAllTy exp tvs (L _ []) ty = mk_forall_ty exp tvs ty<br>
mkHsForAllTy exp tvs (L _ []) ty = HsForAllTy exp Nothing (mkHsQTvs tvs) (L noSrcSpan []) ty<br>
mkHsForAllTy exp tvs ctxt     ty = HsForAllTy exp extra   (mkHsQTvs tvs) cleanCtxt        ty<br>
  where -- Separate the extra-constraints wildcard when present<br>
        (cleanCtxt, extra)<br>
          | (L l HsWildcardTy) <- ignoreParens (last (unLoc ctxt)) = (init `fmap` ctxt, Just l)<br>
          | otherwise = (ctxt, Nothing)<br>
        ignoreParens (L _ (HsParTy ty)) = ty -- TODO:AZ We lose the annotation here<br>
        ignoreParens ty                 = ty<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><br>
I get the following errors in the stage 2 compile (only first 3 shown here)<br>
<br>
<br>
libraries/ghc-prim/GHC/Classes.hs:52:19:<br>
    Malformed instance: (Eq a, Eq b) => Eq (a, b)<br>
<br>
libraries/ghc-prim/GHC/Classes.hs:53:19:<br>
    Malformed instance: (Eq a, Eq b, Eq c) => Eq (a, b, c)<br>
<br>
libraries/ghc-prim/GHC/Classes.hs:54:19:<br>
    Malformed instance: (Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d)<br>
<br>
<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:6.0pt">Alan<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-bottom:6.0pt"> <u></u><u></u></p>
<div>
<p class="MsoNormal" style="margin-bottom:6.0pt">On Fri, Apr 10, 2015 at 12:14 AM, Simon Peyton Jones <<a href="mailto:simonpj@microsoft.com" target="_blank">simonpj@microsoft.com</a>> wrote:<u></u><u></u></p>
<blockquote style="border:none;border-left:solid #cccccc 1.0pt;padding:0cm 0cm 0cm 6.0pt;margin-left:4.8pt;margin-top:5.0pt;margin-right:0cm;margin-bottom:5.0pt">
<div>
<div>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:"Calibri",sans-serif;color:#1f497d">Hmm.  I’m not sure what the motivation is either.  Try dropping it out and see if anything goes wrong.</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:"Calibri",sans-serif;color:#1f497d"><br>
Simon</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:11.0pt;font-family:"Calibri",sans-serif;color:#1f497d"> </span><u></u><u></u></p>
<div style="border:none;border-left:solid blue 1.5pt;padding:0cm 0cm 0cm 4.0pt">
<div>
<div style="border:none;border-top:solid #e1e1e1 1.0pt;padding:3.0pt 0cm 0cm 0cm">
<p class="MsoNormal"><b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US">From:</span></b><span style="font-size:11.0pt;font-family:"Calibri",sans-serif" lang="EN-US"> ghc-devs
 [mailto:<a href="mailto:ghc-devs-bounces@haskell.org" target="_blank">ghc-devs-bounces@haskell.org</a>]
<b>On Behalf Of </b>Alan & Kim Zimmerman<br>
<b>Sent:</b> 09 April 2015 22:15<br>
<b>To:</b> <a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
<b>Subject:</b> Collapsing HsForAllTy, again</span><u></u><u></u></p>
</div>
</div>
<div>
<div>
<p class="MsoNormal"> <u></u><u></u></p>
<div>
<div>
<div>
<div>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">With the help of Jan Stolarek I tracked down the HsForAllTy flattening to<br>
 `HsTypes.mk_forall_ty`.</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">This function takes any nested HsForAllTy's where the top one does not have a context defined, and collapses them into a single one.</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">I do not know what the motivation for this is, and if it perhaps speeds up or simplifies further compilation.</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">But now that API Annotations have arrived, making sure we do not lose the annotations for the sub-HsForAllTy  causes significant gymnastics
 in the parser [1].</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">So my question is, is there a good reason to continue doing this, given the trade-off in parser complexity.</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:6.0pt"><span style="font-family:"Arial",sans-serif">Regards</span><u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">  Alan</span><u></u><u></u></p>
<div>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><span style="font-family:"Arial",sans-serif">[1]</span> 
<a href="https://phabricator.haskell.org/D833" target="_blank">https://phabricator.haskell.org/D833</a><u></u><u></u></p>
<div>
<div>
<p class="MsoNormal" style="margin-bottom:6.0pt"> <u></u><u></u></p>
</div>
</div>
</div>
</div>
</div>
</div>
</div>
</div>
</div>
</div>
</div>
</div>
</blockquote>
</div>
<p class="MsoNormal"> <u></u><u></u></p>
</div>
</div>
</div>
</div>
</div>
</div>
</blockquote>
</div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
</div>
</div>
</blockquote>
</div>
<p class="MsoNormal"><u></u> <u></u></p>
</div>
</div></div></div>
</div>
</div>

</blockquote></div><br></div>