Panic when using syb with GHC API

Simon Hengel simon.hengel at wiktory.org
Thu Aug 25 00:11:34 CEST 2011


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



More information about the Glasgow-haskell-users mailing list