 
            Hello, I'm using the GHC lexer to parse some haskell code containing a language pragma, in GHC 7.4.2 module Main where import GHC import GHC.Paths ( libdir ) import Lexer import qualified MonadUtils as GMU import StringBuffer import FastString (mkFastString) import SrcLoc import ErrUtils (mkPlainErrMsg) main::IO() main = do let contents="{-# LANGUAGE CPP #-}\nmodule Main where\nmain=undefined" runGhc (Just libdir) $ do flg <- getSessionDynFlags let sb=stringToStringBuffer contents let lexLoc = mkRealSrcLoc (mkFastString "<interactive>") 1 1 let prTS = lexTokenStream sb lexLoc flg case prTS of POk _ toks -> GMU.liftIO $ print $ map (show . unLoc) toks PFailed l msg -> GMU.liftIO $ print $ mkPlainErrMsg l msg This prints: ["ITblockComment \" CPP #\"","ITmodule","ITconid \"Main\"","ITwhere","ITvocurly","ITvarid \"main\"","ITequal","ITvarid \"undefined\""] Why is the first token ITblockComment and not ITlanguage_prag? Do I need to enable something special to get pragma tokens? Thanks! -- JP Moresmau http://jpmoresmau.blogspot.com/