Extracting comments from the source code

Santiago Weight santiago.weight at gmail.com
Fri Jan 27 22:47:47 UTC 2023


I’m not sure why you expect it to be so slow? When developing refactoring
tasks for HLS I have never noticed big latencies, even when performing
multiple generic traversals over a full module.

You might have some success by specializing or inking the definition, so
that GHC can optimize the traversal generated.

Best

Santi

On Friday, 27 January 2023, Facundo Domínguez <facundo.dominguez at tweag.io>
wrote:

> Dear GHC devs,
>
> I'm trying to port Liquid Haskell to ghc 9.2.5. And having much difficulty
> using the GHC API for a specific task, so I come here to ask about it.
>
> As you may know already, Liquid Haskell needs to read special comments
> from Haskell source code which have the form {-@ ... @-}.
>
> For example
>
> > module Demo.Lib where
> >
> > {-@ type Pos = {v:Int | 0 < v} @-}
> >
> > {-@ incr :: Pos -> Pos @-}
> > incr :: Int -> Int
> > incr x = h x
> >   where
> >      {-@ h :: Pos -> Pos @-}
> >      h x = x - 1
>
> Since Liquid Haskell runs as a GHC plugin, it has access to the GHC API.
> It used to be the case that one could find all of the comments together
> with their source spans in a field
>
> pm_annotations :: ParsedModule -> ApiAnns -- [1]
>
> However this field has been removed in ghc-9.2, and now the comments are
> all spread through the AST after parsing.
>
> I managed to collect them all again with a generic traversal:
>
> > go :: forall a. Data a => a -> [LEpaComment]
> > go = gmapQr (++) [] go `extQ` (id @[LEpaComment])
>
> but I'd expect this to be rather slow. So I'd like to ask here, is there a
> better way to collect all of the comments?
>
> The other obvious way would be to write the traversal manually, but it
> would be some code to write, and it would likely need attention when
> porting to newer GHCs onwards.
>
> Thanks!
> Facundo
>
> [1]: https://hackage.haskell.org/package/ghc-9.0.2/docs/GHC.
> html#t:ParsedModule
>
>
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20230127/212dbeb3/attachment.html>


More information about the ghc-devs mailing list