Panic when using syb with GHC API

José Pedro Magalhães jpm at cs.uu.nl
Fri Aug 26 11:18:07 CEST 2011


Hi,

On Fri, Aug 26, 2011 at 10:22, Simon Peyton-Jones <simonpj at microsoft.com>wrote:

> Feel free to propose better solutions.
>

I see the problem, but it's indeed not clear how to improve the current
situation.

Adding one more possible solution: SYB, as it is, will traverse the entire
data structure, even if it is clear (from the types) that there will be
nothing to transform inside a certain term.

A while ago, Claus Reinke developed a different form of traversals for SYB,
which avoid entering subterms when it is clear that there is nothing to
transform there. You can see the code in a branch of the current repo:
https://github.com/dreixel/syb/blob/gps/src/Data/Generics/GPS.hs

Maybe using this could help, since then SYB would not traverse everything.
In general, however, this is still not a complete solution, because you
might have written a traversal which does intend to operate inside these
undefined values: you just don't expect them to be undefined.

In any case, maybe Simon Hengel can try using this. If it seems like this
avoids the problem, I'd be happy to release a new version of SYB containing
these type-guided traversals. (Also, for traversing these kind of big
structures, using Claus's traversals might improve performance
considerably.)


Cheers,
Pedro


>
> The underlying issue is that before type checking GHC (obviously) doesn't
> know the types of things, while afterwards it does.  The whole HsSyn tree is
> parameterised over the types of identifiers:
>
>  Parsed:       HsExpr RdrNames
>  Renamed:      HsExpr Name
>  Typechecked:  HsExpr Id
>
> One alternative would be to parameterise the tree over the type of
> type-decorations, so instead of 'PostTcType' you'd have 'ty' (a variable)
> instead.  So we'd have
>
>  Renamed:     HsExpr Name ()
>  Typechecked: HsExpr Id   Type
>
> To me this seems like a bit of a sledgehammer to crack a nut; and I think
> there are a couple of other similar things (like SyntaxExpr).  But it might
> be possible.
>
> Another possibility would be for those PostTcTypes to be (Maybe Type),
> which would be less convenient when you know they are there.
>
> Simon
>
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org [mailto:
> glasgow-haskell-users-
> | bounces at haskell.org] On Behalf Of Ranjit Jhala
> | Sent: 25 August 2011 22:47
> | To: Thomas Schilling
> | Cc: glasgow-haskell-users at haskell.org
> | Subject: Re: Panic when using syb with GHC API
> |
> | Hi,
> |
> | I ran into a similar issue earlier -- you might also look at this
> |
> |       http://mistuke.wordpress.com/category/vsx/
> |
> | (also linked from http://haskell.org/haskellwiki/GHC/As_a_library#Links)
> |
> | Hope to elaborate the text there one of these days...
> |
> | Ranjit.
> |
> |
> | On Aug 25, 2011, at 2:22 AM, Thomas Schilling wrote:
> |
> | > GHC's parse tree contains lots of placeholders.  You are not supposed
> | > to look at them until a specific phase has been run.  For example,
> | > anything of type "SyntaxExpr" is an error thunk until the renamer has
> | > been run.  Unfortunately, SyntaxExpr is just a type synonym, so
> | > there's no way to distinguish them via SYB.
> | >
> | > The simplest workaround is to adapt the default traversal code for the
> | > nodes which may contain such error thunks.  A better solution would be
> | > to change the GHC AST to wrap such possibly undefined nodes with
> | > newtypes, but that would only take effect once the next version of GHC
> | > is released.
> | >
> | > On 24 August 2011 23:11, Simon Hengel <simon.hengel at wiktory.org>
> wrote:
> | >> Hello,
> | >> I'm trying to query a type-checked module with syb, this works for a
> | >> plain binding.  But as soon as I add a type signature for that
> binding,
> | >> I get an "panic!"
> | >>
> | >> I experienced similar problems with a renamed module.
> | >>
> | >> Are those data structures meant to be used with syb?  And if yes, what
> | >> did I miss?
> | >>
> | >> Bellow is some code to reproduce my issue.  Any help is very much
> | >> appreciated.
> | >>
> | >>    -- A.hs
> | >>    module Main where
> | >>
> | >>    import GHC
> | >>    import Outputable
> | >>    import Data.Generics
> | >>    import GHC.Paths (libdir)
> | >>
> | >>    import Bag
> | >>
> | >>    main :: IO ()
> | >>    main = do
> | >>      m <- parse
> | >>      putStrLn $ showSDoc $ ppr $ m
> | >>      putStrLn "\n---\n"
> | >>      putStrLn $ showSDoc $ ppr $ selectAbsBinds m
> | >>
> | >>    parse = runGhc (Just libdir) $ do
> | >>      _ <- getSessionDynFlags >>= setSessionDynFlags
> | >>      target <- guessTarget "B.hs" Nothing
> | >>      setTargets [target]
> | >>      Succeeded <- load LoadAllTargets
> | >>      modSum <- getModSummary $ mkModuleName "B"
> | >>      m <- parseModule modSum >>= typecheckModule
> | >>      return $ typecheckedSource m
> | >>
> | >>    selectAbsBinds :: GenericQ [HsBindLR Id Id]
> | >>    selectAbsBinds = everything (++) ([] `mkQ` f)
> | >>      where
> | >>        f x@(AbsBinds _ _ _ _ _) = [x]
> | >>        f _ = []
> | >>
> | >>
> | >>    -- B.hs
> | >>    module B where
> | >>
> | >>    foo :: Char
> | >>    foo = 'f'
> | >>
> | >> Cheers,
> | >> Simon
> | >>
> | >> _______________________________________________
> | >> Glasgow-haskell-users mailing list
> | >> Glasgow-haskell-users at haskell.org
> | >> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> | >>
> | >
> | >
> | >
> | > --
> | > Push the envelope. Watch it bend.
> | >
> | > _______________________________________________
> | > Glasgow-haskell-users mailing list
> | > Glasgow-haskell-users at haskell.org
> | > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> |
> |
> | _______________________________________________
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users at haskell.org
> | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20110826/181f1ef0/attachment.htm>


More information about the Glasgow-haskell-users mailing list