<div dir="ltr"><div>I think this is a good idea<br><br></div>Alan<br></div><div class="gmail_extra"><br><div class="gmail_quote">On Wed, Oct 28, 2015 at 12:17 AM, 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;color:#1f497d">Ahh. I think I get it.  The trouble is that ConDecl doesn’t have the same structure as what the user wrote.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d">Maybe we should just fix that?  How about this declaration?  Would that make the annotations easier?  Ie simple and routine.<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"><u></u> <u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d">Simon<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"><u></u> <u></u></span></p>
<p><span>data ConDecl name<u></u><u></u></span></p>
<p><span>  | ConDeclGADT<u></u><u></u></span></p>
<p><span>      { con_names   :: [Located name]<u></u><u></u></span></p>
<p><span>      , con_type    :: LHsSigType name  -- After the ‘::’<u></u><u></u></span></p>
<p><span>      , con_doc     :: Maybe LHsDocString<u></u><u></u></span></p>
<p><span>      , con_old_rec :: Bool }<u></u><u></u></span></p>
<p><span><u></u> <u></u></span></p>
<p><span>  | ConDeclH98<u></u><u></u></span></p>
<p><span>      { con_name    :: Located name<u></u><u></u></span></p>
<p><span><u></u> <u></u></span></p>
<p><span>      , con_implict  :: HsImplicitBndrs ()<u></u><u></u></span></p>
<p><span>        -- ^ Implicit binders, added by renamer<u></u><u></u></span></p>
<p><span><u></u> <u></u></span></p>
<p><span>      , con_qvars     :: Maybe [LHsTyVarBndr name]<u></u><u></u></span></p>
<p><span>        --  User-written foralls (if any)<u></u><u></u></span></p>
<p><span><u></u> <u></u></span></p>
<p><span>      , con_cxt       :: Maybe (LHsContext name)<u></u><u></u></span></p>
<p><span>        -- ^ User-written context (if any)<u></u><u></u></span></p>
<p><span><u></u> <u></u></span></p>
<p><span>      , con_details   :: HsConDeclDetails name<u></u><u></u></span></p>
<p><span>          -- ^ Arguments<u></u><u></u></span></p>
<p><span><u></u> <u></u></span></p>
<p><span>      , con_doc       :: Maybe LHsDocString<u></u><u></u></span></p>
<p><span>          -- ^ A possible Haddock comment.<u></u><u></u></span></p>
<p><span>      } deriving (Typeable)<u></u><u></u></span></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"><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> 27 October 2015 21:36<br>
<b>To:</b> Simon Peyton Jones<br>
<b>Subject:</b> Re: dll-split<u></u><u></u></span></p>
</div>
</div>
<p class="MsoNormal"><u></u> <u></u></p>
<div>
<div>
<div>
<div>
<div>
<div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
The problem comes in mkGadtDecl, I am pretty sure.<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
If I compare your branch to master, I see that the old one was<br>
<br>
mkGadtDecl :: [Located RdrName]<br>
           -> LHsType RdrName     -- Always a HsForAllTy<br>
           -> P ([AddAnn], ConDecl RdrName)<br>
mkGadtDecl names (L l ty) = do<br>
  let<br>
    (anns,ty') = flattenHsForAllTyKeepAnns ty<br>
  gadt <- mkGadtDecl' names (L l ty')<br>
  return (anns,gadt)<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
where the flattenHsForAllTyKeepAnns explicitly pulls out annotations that will get lost when the original type gets broken apart and re-assembled as a ConDecl for the GADT.<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
I do recall having to exercise particular care in this area the first time around, because of the way the original type is turned into a GADT constructor.<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-right:0cm;margin-bottom:12.0pt;margin-left:0cm">
If this does not help, I can try and dive into what you are doing in more detail tomorrow afternoon some time.<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:12.0pt;margin-left:0cm">
<u></u> <u></u></p>
</div>
</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 Tue, Oct 27, 2015 at 11:22 PM, 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;color:#1f497d">Thanks.  But why?!  Here’s my reasoning, looking at Parser.y</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"> </span><u></u><u></u></p>
<p><span style="font-family:Symbol;color:#1f497d">·</span><span style="font-size:7.0pt;color:#1f497d">        
</span><span style="font-family:"Calibri",sans-serif;color:#1f497d">The RHS of the GADT signature is a ‘ctype’</span><u></u><u></u></p>
<p><span style="font-family:Symbol;color:#1f497d">·</span><span style="font-size:7.0pt;color:#1f497d">        
</span><span style="font-family:"Calibri",sans-serif;color:#1f497d">That parses the “forall v a.”  , and then goes to type, then btype, then atype</span><u></u><u></u></p>
<p><span style="font-family:Symbol;color:#1f497d">·</span><span style="font-size:7.0pt;color:#1f497d">        
</span><span style="font-family:"Calibri",sans-serif;color:#1f497d">Now we get to the production ‘(‘ ctype ‘)’ in atype</span><u></u><u></u></p>
<p><span style="font-family:Symbol;color:#1f497d">·</span><span style="font-size:7.0pt;color:#1f497d">        
</span><span style="font-family:"Calibri",sans-serif;color:#1f497d">And that has mop and mcp to record the location of the parens.</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d">It all looks right to me.   But NB that now HsForAllTy and HsQualTy are split, so the parens will be attached to the
 HsQualTy sub-structure.  Does that make a difference?</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d"> </span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-family:"Calibri",sans-serif;color:#1f497d">Simon</span><u></u><u></u></p>
<p class="MsoNormal"><span style="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"> Alan
 & Kim Zimmerman [mailto:<a href="mailto:alan.zimm@gmail.com" target="_blank">alan.zimm@gmail.com</a>]
<br>
<b>Sent:</b> 27 October 2015 21:04<br>
<b>To:</b> Simon Peyton Jones<br>
<b>Subject:</b> Re: dll-split</span><u></u><u></u></p>
</div>
</div>
<div>
<div>
<p class="MsoNormal"> <u></u><u></u></p>
<div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt">I have run the tests on your branch, and can report the following for the failing API annotations tests<br>
<br>
   .  T10268 [bad stdout] (normal)     - Benign<br>
   .  T10354 [bad stdout] (normal)     - Benign<br>
   .  T10396 [bad stdout] (normal)     - Benign <br>
   .  T10399 [bad stdout] (normal)     - Problem<br>
   .  listcomps [bad stdout] (normal)   - Benign<u></u><u></u></p>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt">For T10399 the problem is the following are missing<br>
<br>
(AK Test10399.hs:(16,5)-(17,69) AnnCloseP = [Test10399.hs:17:69])<br>
(AK Test10399.hs:(16,5)-(17,69) AnnOpenP = [Test10399.hs:16:27])<u></u><u></u></p>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt">These are the outer parens in SetTo4 after the forall :<br>
<br>
    data MaybeDefault v where<br>
        SetTo :: forall v . ( Eq v, Show v ) => !v -> MaybeDefault v<br>
        SetTo4 :: forall v a. (( Eq v, Show v ) => v -> MaybeDefault v<br>
                                                -> a -> MaybeDefault [a])<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt">I will be documenting the check-api-annotations usage soon, and as part of that will clean it up so that it does not emit gratuitous changes that are benign.<u></u><u></u></p>
</div>
<div>
<p class="MsoNormal" style="margin-bottom:6.0pt">Regards<u></u><u></u></p>
</div>
<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>
<div>
<p class="MsoNormal" style="margin-bottom:12.0pt"> <u></u><u></u></p>
</div>
</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 Tue, Oct 27, 2015 at 11:21 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-family:"Calibri",sans-serif">Incidentally, Alan, on this particular branch I have some api-annotations failures that I can’t figure out (lacking the user manual
 that you are writing).  I wonder if you could help.  Could you possibly build that branch for yourself too? 
</span>wip/spj-wildcard-refactor<u></u><u></u></p>
<p class="MsoNormal"> <u></u><u></u></p>
<p class="MsoNormal">Then I can ask you specifics and you’ll have a working branch to poke at.  Thanks!<u></u><u></u></p>
<p class="MsoNormal"> <u></u><u></u></p>
<p class="MsoNormal">Simon<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"> </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> 27 October 2015 09:12<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>; Ben Gamari<br>
<b>Subject:</b> Re: dll-split</span><u></u><u></u></p>
</div>
</div>
<p class="MsoNormal"> <u></u><u></u></p>
<p>I think you need to remove Ctype and Lexer from <a href="https://na01.safelinks.protection.outlook.com/?url=https%3a%2f%2fgithub.com%2fghc%2fghc%2fblob%2fmaster%2fcompiler%2fghc.mk%23L498&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c9495c042f5744f72c76b08d2deaebda0%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=QHToZ5WZNoTWBYKahSTsaT6Zo%2ftoPgoi%2fP8ybp2FwEQ%3d" target="_blank">
https://github.com/ghc/ghc/blob/master/compiler/ghc.mk#L498</a><u></u><u></u></p>
<div>
<div>
<div>
<p class="MsoNormal">On 27 Oct 2015 11:06 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">It’s just not my day.<u></u><u></u></p>
<p class="MsoNormal">Now, on Linux, on my branch wip/spj-wildcard-refactor, I get a failure in dll-split!  Should dll-split be running at all on Linux????<u></u><u></u></p>
<p class="MsoNormal">The output it produces is below.<u></u><u></u></p>
<p class="MsoNormal">I’m totally stuck.  Help desperately needed.<u></u><u></u></p>
<p class="MsoNormal">Simon<u></u><u></u></p>
<p class="MsoNormal"> <u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:10.0pt;font-family:"Courier New"">inplace/bin/dll-split compiler/stage2/build/.depend-v-p-dyn.haskell "DynFlags" "Annotations ApiAnnotation Avail Bag BasicTypes
 Binary BooleanFormula BreakArray BufWrite Class CmdLineParser CmmType CoAxiom ConLike Coercion Config Constants CoreArity CoreFVs CoreSubst CoreSyn CoreTidy CoreUnfold CoreUtils CoreSeq CoreStats CostCentre Ctype DataCon Demand Digraph DriverPhases DynFlags
 Encoding ErrUtils Exception FamInstEnv FastFunctions FastMutInt FastString FastStringEnv FieldLabel Fingerprint FiniteMap ForeignCall Hooks HsBinds HsDecls HsDoc HsExpr HsImpExp HsLit PlaceHolder HsPat HsSyn HsTypes HsUtils HscTypes IOEnv Id IdInfo IfaceSyn
 IfaceType InstEnv Kind Lexeme Lexer ListSetOps Literal Maybes MkCore MkId Module MonadUtils Name NameEnv NameSet OccName OccurAnal OptCoercion OrdList Outputable PackageConfig Packages Pair Panic PatSyn PipelineMonad Platform PlatformConstants PprCore PrelNames
 PrelRules Pretty PrimOp RdrName Rules Serialized SrcLoc StaticFlags StringBuffer TcEvidence TcRnTypes TcType TrieMap TyCon Type TypeRep TysPrim TysWiredIn Unify UniqFM UniqSet UniqSupply Unique Util Var VarEnv VarSet Bitmap BlockId ByteCodeAsm ByteCodeInstr
 ByteCodeItbls CLabel Cmm CmmCallConv CmmExpr CmmInfo CmmMachOp CmmNode CmmSwitch CmmUtils CodeGen.Platform CodeGen.Platform.ARM CodeGen.Platform.ARM64 CodeGen.Platform.NoRegs CodeGen.Platform.PPC CodeGen.Platform.PPC_Darwin CodeGen.Platform.SPARC CodeGen.Platform.X86
 CodeGen.Platform.X86_64 Hoopl Hoopl.Dataflow InteractiveEvalTypes MkGraph PprCmm PprCmmDecl PprCmmExpr Reg RegClass SMRep StgCmmArgRep StgCmmClosure StgCmmEnv StgCmmLayout StgCmmMonad StgCmmProf StgCmmTicky StgCmmUtils StgSyn Stream"</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:10.0pt;font-family:"Courier New"">Reachable modules from DynFlags out of date</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:10.0pt;font-family:"Courier New"">Please fix compiler/<a href="https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fghc.mk&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c9495c042f5744f72c76b08d2deaebda0%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=R3DAxxzLCBm%2fX7FLV2j9cSLHq7%2bPpcFwvmYGGV5Z1kI%3d" target="_blank">ghc.mk</a>,
 or building DLLs on Windows may break (#7780)</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:10.0pt;font-family:"Courier New"">Redundant modules: Ctype Lexer      
</span><u></u><u></u></p>
<p class="MsoNormal"><span style="font-size:10.0pt;font-family:"Courier New"">simonpj@cam-05-unx:~/5builds/HEAD-2$</span><u></u><u></u></p>
</div>
</div>
<p class="MsoNormal" style="margin-bottom:12.0pt"><br>
_______________________________________________<br>
ghc-devs mailing list<br>
<a href="mailto:ghc-devs@haskell.org" target="_blank">ghc-devs@haskell.org</a><br>
<a href="https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-devs&data=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c9495c042f5744f72c76b08d2deaebda0%7c72f988bf86f141af91ab2d7cd011db47%7c1&sdata=rqxhOhBpRsgtNWoTZbUyssa4RfOaCeh8b8Aza8knm%2fM%3d" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs</a><u></u><u></u></p>
</blockquote>
</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>
</div>

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