
Hi, I'm trying to use GHC API to parse Haskell source code and get an AST but get a "Parse: noRebindableInfo" error. So far my program can parse the simplest code: module HelloWorld where main = do putStrLn $ show "hello" But when I change the show "hello" to show 0, eg, try to parse the following code: module HelloWorld where main = do putStrLn $ show 0 I get a "Parse: noRebindableInfo" error (or exception?) and nothing in the output file. I must did something wrong, but I can't figure out it. The following is my program (highlighted source code here: http://pastebin.com/f556455ff ). I compiled it with "ghc --make -package ghc Parse.hs". The GHC version I used is 6.10.2. After compiled, I run the following command to execute the program: "./Parse hello.hs test.out" where test.out is the output file for the AST. ------------------------------------------------------------------------------------------------------------- module Main where import qualified Parser import StringBuffer import Lexer import FastString import SrcLoc import DynFlags import StaticFlagParser import HscTypes import GHC import GHC.SYB.Utils import System import IO doParse infile dflags = do buf <- hGetStringBuffer infile let loc = mkSrcLoc (mkFastString infile) 1 0 return $ unP Parser.parseModule (mkPState buf loc dflags) parseFile infile = defaultErrorHandler defaultDynFlags $ {-defaultCleanupHandler $-} runGhc (Just "/usr/lib/ghc-6.10.2/") $ do hsc_env <- getSession let dflags0 = hsc_dflags hsc_env let dflags = dflags0{ verbosity = 99 } setSessionDynFlags dflags handleSourceError (\e -> do printExceptionAndWarnings e liftIO $ exitWith (ExitFailure 1)) $ do liftIO $ doParse infile dflags main :: IO () main = do args <- getArgs let [infile, outfile] = args hSetBuffering stdout NoBuffering res <- parseFile infile case res of POk _ x -> bracket (openFile outfile WriteMode) hClose (\h -> hPutStrLn h $ showData Parser 2 x) PFailed loc err -> do hPutStrLn stderr $ "Failure when parsing " ++ show infile ++ ": " -- ++ show err {-exitWith (ExitFailure (-1))-} ------------------------------------------------------------------------------------------------------------- The actual output of the program is: ------------------------------------------------------------------------------------------------------------- Using package config file: /usr/lib/ghc-6.10.2/package.conf hiding package base-3.0.3.1 to avoid conflict with later version base-4.1.0.0 wired-in package ghc-prim mapped to ghc-prim-0.1.0.0 wired-in package integer mapped to integer-0.1.0.1 wired-in package base mapped to base-4.1.0.0 wired-in package rts mapped to rts-1.0 wired-in package haskell98 mapped to haskell98-1.0.1.0 wired-in package syb mapped to syb-0.1.0.1 wired-in package template-haskell mapped to template-haskell-2.3.0.1 wired-in package dph-seq mapped to dph-seq-0.3 wired-in package dph-par mapped to dph-par-0.3 Parse: noRebindableInfo ------------------------------------------------------------------------------------------------------------- Thank you very much! -- Haoyu Bai