GADT decls

Simon Peyton Jones simonpj at microsoft.com
Tue Oct 27 22:17:42 UTC 2015


Ahh. I think I get it.  The trouble is that ConDecl doesn’t have the same structure as what the user wrote.

Maybe we should just fix that?  How about this declaration?  Would that make the annotations easier?  Ie simple and routine.

Simon


data ConDecl name

  | ConDeclGADT

      { con_names   :: [Located name]

      , con_type    :: LHsSigType name  -- After the ‘::’

      , con_doc     :: Maybe LHsDocString

      , con_old_rec :: Bool }



  | ConDeclH98

      { con_name    :: Located name



      , con_implict  :: HsImplicitBndrs ()

        -- ^ Implicit binders, added by renamer



      , con_qvars     :: Maybe [LHsTyVarBndr name]

        --  User-written foralls (if any)



      , con_cxt       :: Maybe (LHsContext name)

        -- ^ User-written context (if any)



      , con_details   :: HsConDeclDetails name

          -- ^ Arguments



      , con_doc       :: Maybe LHsDocString

          -- ^ A possible Haddock comment.

      } deriving (Typeable)

From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com]
Sent: 27 October 2015 21:36
To: Simon Peyton Jones
Subject: Re: dll-split

The problem comes in mkGadtDecl, I am pretty sure.
If I compare your branch to master, I see that the old one was

mkGadtDecl :: [Located RdrName]
           -> LHsType RdrName     -- Always a HsForAllTy
           -> P ([AddAnn], ConDecl RdrName)
mkGadtDecl names (L l ty) = do
  let
    (anns,ty') = flattenHsForAllTyKeepAnns ty
  gadt <- mkGadtDecl' names (L l ty')
  return (anns,gadt)
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.
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.
If this does not help, I can try and dive into what you are doing in more detail tomorrow afternoon some time.
Alan



On Tue, Oct 27, 2015 at 11:22 PM, Simon Peyton Jones <simonpj at microsoft.com<mailto:simonpj at microsoft.com>> wrote:
Thanks.  But why?!  Here’s my reasoning, looking at Parser.y


•         The RHS of the GADT signature is a ‘ctype’

•         That parses the “forall v a.”  , and then goes to type, then btype, then atype

•         Now we get to the production ‘(‘ ctype ‘)’ in atype

•         And that has mop and mcp to record the location of the parens.

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?

Simon

From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com<mailto:alan.zimm at gmail.com>]
Sent: 27 October 2015 21:04
To: Simon Peyton Jones
Subject: Re: dll-split

I have run the tests on your branch, and can report the following for the failing API annotations tests

   .  T10268 [bad stdout] (normal)     - Benign
   .  T10354 [bad stdout] (normal)     - Benign
   .  T10396 [bad stdout] (normal)     - Benign
   .  T10399 [bad stdout] (normal)     - Problem
   .  listcomps [bad stdout] (normal)   - Benign
For T10399 the problem is the following are missing

(AK Test10399.hs:(16,5)-(17,69) AnnCloseP = [Test10399.hs:17:69])
(AK Test10399.hs:(16,5)-(17,69) AnnOpenP = [Test10399.hs:16:27])
These are the outer parens in SetTo4 after the forall :

    data MaybeDefault v where
        SetTo :: forall v . ( Eq v, Show v ) => !v -> MaybeDefault v
        SetTo4 :: forall v a. (( Eq v, Show v ) => v -> MaybeDefault v
                                                -> a -> MaybeDefault [a])
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.
Regards
  Alan



On Tue, Oct 27, 2015 at 11:21 AM, Simon Peyton Jones <simonpj at microsoft.com<mailto:simonpj at microsoft.com>> wrote:
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?  wip/spj-wildcard-refactor

Then I can ask you specifics and you’ll have a working branch to poke at.  Thanks!

Simon


From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com<mailto:alan.zimm at gmail.com>]
Sent: 27 October 2015 09:12
To: Simon Peyton Jones
Cc: ghc-devs at haskell.org<mailto:ghc-devs at haskell.org>; Ben Gamari
Subject: Re: dll-split


I think you need to remove Ctype and Lexer from https://github.com/ghc/ghc/blob/master/compiler/ghc.mk#L498<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>
On 27 Oct 2015 11:06 AM, "Simon Peyton Jones" <simonpj at microsoft.com<mailto:simonpj at microsoft.com>> wrote:
It’s just not my day.
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????
The output it produces is below.
I’m totally stuck.  Help desperately needed.
Simon

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"
Reachable modules from DynFlags out of date
Please fix compiler/ghc.mk<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>, or building DLLs on Windows may break (#7780)
Redundant modules: Ctype Lexer
simonpj at cam-05-unx:~/5builds/HEAD-2$

_______________________________________________
ghc-devs mailing list
ghc-devs at haskell.org<mailto:ghc-devs at haskell.org>
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs<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>


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20151027/a5e145fd/attachment-0001.html>


More information about the ghc-devs mailing list