[Haskell-cafe] Problem with reloading modules in GHC API
Hongmin Fan
hongmin.fan.lists at gmail.com
Mon Jul 19 23:12:38 EDT 2010
Hi,
I'm using GHC API to dynamically load some module, and evaluate it; and
later change the content of the module, and re-evaluate it. But I found
unless I delete the object file created by previous compilation, the module
seems not reloaded. I have set ghcLink = LinkInMemory as an older post
suggested
To illustrate what I'm saying, here is a piece of code (sorry for any
naivety in the code, new to Haskell too)
import System.IO (IOMode(..),hClose,hPutStr,openFile)
import Directory (removeFile)
import GHC
import GHC.Paths
import DynFlags
import Unsafe.Coerce
src_file = "Target.hs"
obj_file = "Target.o"
main = do
writeTarget "arg"
func0 <- compileTarget
putStrLn $ show $ func0 2
writeTarget "arg*2"
func1 <- compileTarget
putStrLn $ show $ func1 2
writeTarget input = do
-- removeFile obj_file `catch` (const $ return ()) -- uncomment this line
to have correct results
h <- openFile src_file WriteMode
hPutStr h "module Target (Target.target) where\n"
hPutStr h "target::Double -> Double\n"
hPutStr h "target arg = \n "
hPutStr h input
hClose h
compileTarget =
defaultErrorHandler defaultDynFlags $ do
func <- runGhc (Just libdir) $ do
-- setup dynflags
dflags <- getSessionDynFlags
setSessionDynFlags dflags { ghcLink = LinkInMemory }
-- load target module
target <- guessTarget src_file Nothing
setTargets [target]
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
m <- findModule (mkModuleName "Target") Nothing
-- set context and compile
setContext [] [m]
value <- compileExpr ("Target.target")
do
let value' = (unsafeCoerce value) :: Double ->
Double
return value'
return func
The code basically write to a Haskell source file twice with different
content, and hoping to get different results, but unless I uncomment the
line with removeFile, the output of 2 runs are the same; using 'touch' to
touch the source file being written between 2 runs also gives the correct
results. So maybe caused by some caching mechanism?
I'm using GHC 6.12.1 in Ubuntu 10.04. I have this workaround of deleting the
obj file, but I'm wondering the "correct" way of doing it. Did some search
on GHC API, but never got something relevant.
Thanks,
Hongmin
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100719/701f93cb/attachment.html
More information about the Haskell-Cafe
mailing list