
On Oct 25, 2008, at 8:39 PM, Anatoly Yakovenko wrote:
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: [...]
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?
Hi, Anatoly Sorry for don't answering your question in the first place, but for this kind of tasks I believe you might be better off using some lightweight wrapper of the GHC Api. For instance, using http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hint you write: import Language.Haskell.Interpreter.GHC import Control.Monad.Trans ( liftIO ) import Control.Monad ( filterM ) test_module = "Test" main :: IO () main = do s <- newSession withSession s $ do loadModules [test_module] -- loads Test.hs... setTopLevelModules [test_module] -- ...and puts it in scope setImports ["Prelude"] -- put the Prelude in scope too -- exports <- getModuleExports "Test" -- get Test's symbols let ids = [f | Fun f <- exports] -- strings <- filterM (hasType "[Char]") ids conc <- concat `fmap` mapM (\e -> interpret e infer) strings liftIO $ putStrLn conc -- ns <- filterM (hasType "Integer") ids sum_ns <- sum `fmap` mapM (\e -> interpret e (as :: Integer)) ns liftIO $ putStrLn (show sum_ns) hasType :: String -> Id -> Interpreter Bool hasType t e = do type_of_e <- typeOf e return (type_of_e == t) $ ./Main helloworld 3 The version in hackage of hint works only with GHC 6.6.x and 6.8.x, mind you, but a new version is coming soon.... Good luck, Daniel