Feedback request for #9628 AST Annotations

Neil Mitchell ndmitchell at gmail.com
Wed Oct 1 20:23:55 UTC 2014


> I am not sure that I understand your proposal correctly, but I interpret the
> requirement
>  to map the Dynamic type to the TypeRep of the constructor meaning some kind
> of separate
>  linkage between the Constructor and the specific annotation type.

The key is that there is no linkage from the constructor. Instead of
putting ((srcspan,"LetIn"), AnnLetIn ... :: Ann) into the map we put
(srcspan, AnnLetIn ... :: AnnLetIn) in the map. The constructor is
implicitly encoded by the type of the annotation.

> This is a very good reason to break it into separate types. And then the
> reason
>  for the Dynamic becomes clear.

The whole TypeRep/Dynamic thing is just a nice way to encode Map with
multiple value types that don't tread on each other, it's not a detail
the user of the API would ever see.

>
>
>>
>> That said, I'm willing to believe there is some level of generic-ness
>> that is easier to leverage with the single annotation, so I'm not
>> convinced my proposal is necessarily a good idea.
>>
>> > Also, it only relies on the AST being an instance of Data, which already
>> > holds.
>>
>> Mine only relies on the annotation types being an instance of
>> Typeable, which is far less burdensome (although somewhat irrelevant,
>> since both criteria will be met).
>>
>> Thanks, Neil
>>
>>
>> > On Wed, Oct 1, 2014 at 6:37 PM, Neil Mitchell <ndmitchell at gmail.com>
>> > wrote:
>> >>
>> >> I was getting a bit lost between the idea and the implementation. Let
>> >> me try rephrasing the idea in my own words.
>> >>
>> >> The goal: Capture inner source spans in AST syntax nodes. At the
>> >> moment if ... then ... else ... captures the spans [if [...] then
>> >> [...] else [...]]. We want to capture the spans for each keyword as
>> >> well, so: [{if} [...] {then} [...] {else} [...]].
>> >>
>> >> The proposal: Rather than add anything to the AST, have a separate
>> >> mapping (SrcSpan,AstCtor) to [SrcSpan]. So you give in the SrcSpan
>> >> from the IfThenElse node, and some token for the IfThenElse
>> >> constructor, and get back a list of IfThenElse for the particular
>> >> keyword.
>> >>
>> >> I like the proposal because it adds nothing inside the AST, and
>> >> requires no fresh invariants of the AST. I dislike it because the
>> >> contents of that separate mapping are highly tied up with the AST, and
>> >> easy to get out of sync. I think it's the right choice for three
>> >> reasons, 1) it is easier to try out and doesn't break the AST, so we
>> >> have more scope for changing our minds later; 2) the same technique is
>> >> able to represent things other than SrcSpan without introducing a
>> >> polymorphic src span; 3) the people who pay the complexity are the
>> >> people who use it, which is relatively few people.
>> >>
>> >> That said, as a tweak to the API, rather than a single data type for
>> >> all annotations, you could have:
>> >>
>> >> data AnnIfThenElse = AnnIfThenElse {posIf, posThen, posElse :: SrcSpan}
>> >> data AnnDo = AnnDo {posDo :: SrcSpan}
>> >>
>> >> Then you could just have an opaque Map (SrcSpan, TypeRep) Dynamic,
>> >> with the invariant that the TypeRep in the key matches the Dynamic.
>> >> Then you can have: getAnnotation :: Typeable a => Annotations ->
>> >> SrcSpan -> Maybe a. I think it simplifies some of the TypeRep trickery
>> >> you are engaging in with mkAnnKey.
>> >>
>> >> Thanks, Neil
>> >>
>> >> On Wed, Oct 1, 2014 at 5:06 PM, Simon Peyton Jones
>> >> <simonpj at microsoft.com> wrote:
>> >> > Let me urge you, once more, to consult some actual heavy-duty users
>> >> > of
>> >> > these
>> >> > proposed facilities.  I am very keen to avoid investing design and
>> >> > implementation effort in facilities that may not meet the need.
>> >> >
>> >> >
>> >> >
>> >> > If they end up acclaiming the node-key idea, then we should surely
>> >> > simply
>> >> > make the key an abstract type, simply an instance of Hashable, Ord,
>> >> > etc.
>> >> >
>> >> >
>> >> >
>> >> > Simon
>> >> >
>> >> >
>> >> >
>> >> > From: Alan & Kim Zimmerman [mailto:alan.zimm at gmail.com]
>> >> > Sent: 30 September 2014 19:48
>> >> > To: Simon Peyton Jones
>> >> > Cc: Richard Eisenberg; Edward Z. Yang; ghc-devs at haskell.org
>> >> >
>> >> >
>> >> > Subject: Re: Feedback request for #9628 AST Annotations
>> >> >
>> >> >
>> >> >
>> >> > On further reflection of the goals for the annotation, I would like
>> >> > to
>> >> > put
>> >> > forward the following proposal for comment
>> >> >
>> >> >
>> >> > Instead of physically placing a "node-key" in each AST Node, a
>> >> > virtual
>> >> > node key can be generated from any `GenLocated SrcSpan e' comprising
>> >> > a
>> >> > combination of the `SrcSpan` value and a unique identifier from the
>> >> > constructor for `e`, perhaps using its `TypeRep`, since the entire
>> >> > AST
>> >> > derives Typeable.
>> >> >
>> >> > To further reduce the intrusiveness, a base Annotation type can be
>> >> > defined that captures the location of noise tokens for each AST
>> >> > constructor. This can then be emitted from the parser, if the
>> >> > appropriate flag is set to enable it.
>> >> >
>> >> > So
>> >> >
>> >> >     data ApiAnnKey = AK SrcSpan TypeRep
>> >> >
>> >> >     mkApiAnnKey :: (Located e) -> ApiAnnKey
>> >> >     mkApiAnnKey = ...
>> >> >
>> >> >     data Ann =
>> >> >       ....
>> >> >       | AnnHsLet    SrcSpan -- of the word "let"
>> >> >                     SrcSpan -- of the word "in"
>> >> >
>> >> >       | AnnHsDo     SrcSpan -- of the word "do"
>> >> >
>> >> > And then in the parser
>> >> >
>> >> >         | 'let' binds 'in' exp   { mkAnnHsLet $1 $3 (LL $ HsLet
>> >> > (unLoc
>> >> > $2)
>> >> > $4) }
>> >> >
>> >> > The helper is
>> >> >
>> >> >     mkAnnHsLet :: Located a -> Located b -> LHsExpr RdrName -> P
>> >> > (LHsExpr
>> >> > RdrName)
>> >> >     mkAnnHsLet (L l_let _) (L l_in _) e = do
>> >> >       addAnnotation (mkAnnKey e) (AnnHsLet l_let l_in)
>> >> >       return e;
>> >> >
>> >> > The Parse Monad would have to accumulate the annotations to be
>> >> > returned at the end, if called with the appropriate flag.
>> >> >
>> >> > There will be some boilerplate in getting the annotations and helper
>> >> > functions defined, but it will not pollute the rest.
>> >> >
>> >> > This technique can also potentially be backported to support older
>> >> > GHC
>> >> > versions via a modification to ghc-parser.
>> >> >
>> >> >     https://hackage.haskell.org/package/ghc-parser
>> >> >
>> >> > Regards
>> >> >
>> >> >   Alan
>> >> >
>> >> >
>> >> >
>> >> > On Tue, Sep 30, 2014 at 2:04 PM, Alan & Kim Zimmerman
>> >> > <alan.zimm at gmail.com>
>> >> > wrote:
>> >> >
>> >> > I tend to agree that this change is much too intrusive for what it
>> >> > attempts
>> >> > to do.
>> >> >
>> >> > I think the concept of a node key could be workable, and ties in to
>> >> > the
>> >> > approach I am taking in ghc-exactprint [1], which uses a SrcSpan
>> >> > together
>> >> > with node type as the annotation key.
>> >> >
>> >> > [1]  https://github.com/alanz/ghc-exactprint
>> >> >
>> >> >
>> >> >
>> >> > On Tue, Sep 30, 2014 at 11:19 AM, Simon Peyton Jones
>> >> > <simonpj at microsoft.com>
>> >> > wrote:
>> >> >
>> >> > I'm anxious about it being too big a change too.
>> >> >
>> >> > I'd be up for it if we had several "customers" all saying "yes, this
>> >> > is
>> >> > precisely what we need to make our usage of the GHC API far far
>> >> > easier".
>> >> > With enough detail so we can understand their use-case.
>> >> >
>> >> > Otherwise I worry that we might go to a lot of effort to solve the
>> >> > wrong
>> >> > problem; or to build a solution that does not, in the end, work for
>> >> > the
>> >> > actual use-case.
>> >> >
>> >> > Another way to tackle this would be to ensure that syntax tree nodes
>> >> > have a
>> >> > "node-key" (a bit like their source location) that clients could use
>> >> > in
>> >> > a
>> >> > finite map, to map node-key to values of their choice.
>> >> >
>> >> > I have not reviewed your patch in detail, but it's uncomfortable that
>> >> > the
>> >> > 'l' parameter gets into IfGblEnv and DsM.  That doesn't smell right.
>> >> >
>> >> > Ditto DynFlags/HscEnv, though I think here that you are right that
>> >> > the
>> >> > "hooks" interface is very crucial.  After all, the WHOLE POINT is too
>> >> > make
>> >> > the client interface more flexible. I would consult Luite and Edsko,
>> >> > who
>> >> > were instrumental in designing the new hooks interface
>> >> >         https://ghc.haskell.org/trac/ghc/wiki/Ghc/Hooks
>> >> > (I'm not sure if that page is up to date, but I hope so)
>> >> >
>> >> > A good way to proceed might be to identify some of the big users of
>> >> > the
>> >> > GHC
>> >> > API (I'm sure I don't know them all), discuss with them what would
>> >> > help
>> >> > them, and share the results on a wiki page.
>> >> >
>> >> > Simon
>> >> >
>> >> >
>> >> > |  -----Original Message-----
>> >> > |  From: ghc-devs [mailto:ghc-devs-bounces at haskell.org] On Behalf Of
>> >> > |  Richard Eisenberg
>> >> > |  Sent: 30 September 2014 03:04
>> >> > |  To: Edward Z. Yang
>> >> > |  Cc: ghc-devs at haskell.org
>> >> > |  Subject: Re: Feedback request for #9628 AST Annotations
>> >> > |
>> >> > |  I'm only speaking up because Alan is specifically requesting
>> >> > feedback:
>> >> > |  I'm really ambivalent about this. I agree with Edward that this is
>> >> > a
>> >> > |  big change and adds permanent noise in a lot of places. But, I
>> >> > also
>> >> > |  really respect the goal here -- better tool support. Is it
>> >> > worthwhile
>> >> > |  to do this using a dynamically typed bit (using Typeable and
>> >> > such),
>> >> > |  which would avoid the noise? Maybe.
>> >> > |
>> >> > |  What do other languages do? Do we know what, say, Agda does to get
>> >> > |  such tight coupling with an editor? Does, say, Eclipse have such a
>> >> > |  chummy relationship with a Java compiler to do its refactoring, or
>> >> > is
>> >> > |  that separately implemented? Haskell/GHC is not the first project
>> >> > to
>> >> > |  have this problem, and there's plenty of solutions out there. And,
>> >> > |  unlike most other times, I don't think Haskell is exceptional in
>> >> > this
>> >> > |  regard (there's nothing very special about Haskell's AST, maybe
>> >> > beyond
>> >> > |  indentation-awareness), so we can probably adopt other solutions
>> >> > |  nicely.
>> >> > |
>> >> > |  Richard
>> >> > |
>> >> > |  On Sep 29, 2014, at 8:58 PM, "Edward Z. Yang" <ezyang at mit.edu>
>> >> > wrote:
>> >> > |
>> >> > |  > Excerpts from Alan & Kim Zimmerman's message of 2014-09-29
>> >> > 13:38:45
>> >> > |  -0700:
>> >> > |  >> 1. Is this change too big, should I scale it back to just
>> >> > update
>> >> > |  the
>> >> > |  >>   HsSyn structures and then lock it down to Located SrcSpan for
>> >> > all
>> >> > |  >>   the rest?
>> >> > |  >
>> >> > |  > I don't claim to speak for the rest of the GHC developers, but I
>> >> > |  think
>> >> > |  > this change is too big.  I am almost tempted to say that we
>> >> > |  shouldn't
>> >> > |  > add the type parameter at all, and do something else (maybe
>> >> > Backpack
>> >> > |  > can let us extend SrcSpan in a modular way, or even use a
>> >> > |  dynamically
>> >> > |  > typed map for annotations.)
>> >> > |  >
>> >> > |  > Edward
>> >> > |  > _______________________________________________
>> >> > |  > ghc-devs mailing list
>> >> > |  > ghc-devs at haskell.org
>> >> > |  > http://www.haskell.org/mailman/listinfo/ghc-devs
>> >> > |
>> >> > |  _______________________________________________
>> >> > |  ghc-devs mailing list
>> >> > |  ghc-devs at haskell.org
>> >> > |  http://www.haskell.org/mailman/listinfo/ghc-devs
>> >> > _______________________________________________
>> >> > ghc-devs mailing list
>> >> > ghc-devs at haskell.org
>> >> > http://www.haskell.org/mailman/listinfo/ghc-devs
>> >> >
>> >> >
>> >> >
>> >> >
>> >> >
>> >> >
>> >> > _______________________________________________
>> >> > ghc-devs mailing list
>> >> > ghc-devs at haskell.org
>> >> > http://www.haskell.org/mailman/listinfo/ghc-devs
>> >> >
>> >
>> >
>
>


More information about the ghc-devs mailing list