[Haskell-cafe] using ghc as a library

Anatoly Yakovenko aeyakovenko at gmail.com
Sat Oct 25 18:39:18 EDT 2008


so I am trying to figure out how to use ghc as a library.  following
this example, http://www.haskell.org/haskellwiki/GHC/As_a_library, i
can load a module and examine its symbols:

module Main where

import GHC
import GHC.Paths ( libdir )
import DynFlags ( defaultDynFlags )
import System.Environment
import Data.Maybe
import Outputable

main = do
   args <- getArgs
   let file = head $ args
   rv <- defaultErrorHandler defaultDynFlags $ do
      runGhc (Just libdir) $ do
         dflags <- getSessionDynFlags
         setSessionDynFlags dflags
         target <- guessTarget file Nothing
         setTargets [target]
         load LoadAllTargets
         gr <- getModuleGraph
         mi <- getModuleInfo $ ms_mod $ head $ gr
         return $ fromJust $ mi
   print $ showSDoc $ ppr $ modInfoInstances $ rv
   print $ showSDoc $ ppr $ modInfoExports $ rv

given Test.hs:

module Test where

hello = "hello"
world = "world"
one = 1
two = 2

i get this output:

$ ./Main ./Test.hs
"[]"
"[Test.hello, Test.one, Test.two, Test.world]"

which is what i expect.  My question is, how do manipulate the symbols
exported by Test?  Is there a way to test the types?  lets say i
wanted to sum all the numbers and concatenate all the strings in
Test.hs, how would i do that?


More information about the Haskell-Cafe mailing list