
- {-# OPTIONS_GHC -package ghc #-} would be useful, doesn't give a warning, but doesn't work, either. -package works in ghci, but not in source pragmas, why? - hostSession hardcoding topDir doesn't seem to be a good idea. shouldn't GHC export means to get at the "hosting" ghc session (the one compiling the current code), so that one could ask for topDir there? currently, i'm calling "ghc --print-libdir" externally .. if nothing else, perhaps something like the 'ghcDir' hack from the example below could be in GHC? - ppr/printForUser should GHC reexport Outputable? also, ppr doesn't seem to handle infix op definitions correctly, printing the left-hand side in prefix form, but without parentheses? [ghc 6.6.1] claus ----------------------------------------------------- {-# OPTIONS_GHC -package ghc #-} module API where import DynFlags import GHC import System.Process import System.IO import Outputable mode = Interactive -- shouldn't something like this be in System.Process? writer >| cmd = runInteractiveCommand cmd >>= \(i,o,e,p)->writer i cmd |> reader = runInteractiveCommand cmd >>= \(i,o,e,p)->reader o -- shouldn't GHC export a hostSession, -- so that we could ask for things like topDir there? ghcDir = "ghc --print-libdir" |> (fmap dropLineEnds . hGetContents) where dropLineEnds = filter (not . (`elem` "\r\n")) main = defaultErrorHandler defaultDynFlags $ do s <- newSession mode . Just =<< ghcDir flags <- getSessionDynFlags s (flags, _) <- parseDynamicFlags flags ["-package ghc"] GHC.defaultCleanupHandler flags $ do setSessionDynFlags s flags{ hscTarget=HscInterpreted } addTarget s =<< guessTarget "API.hs" Nothing load s LoadAllTargets prelude <- findModule s (mkModuleName "Prelude") Nothing usermod <- findModule s (mkModuleName "API") Nothing setContext s [usermod] [prelude] Just cm <- checkModule s (mkModuleName "API") unqual <- getPrintUnqual s printForUser stdout unqual $ ppr $ parsedSource cm
participants (1)
-
Claus Reinke