
Hi Hongmin,
I think you're looking for how to hot-swap Haskell program.
There are two approach to reach target:
1) Source-Code level:
Recompile source code to build new execute cache file, if re-compile
successful, use executeFile to switch new entry. You perhaps need use
Binary instance to save/restore state between re-launch new execute
file.
2) Dynamic Linking object code.
Compile plugins code to object file, the use .o and .hi file to
dynamic linking object code to running Haskell application.
Because .hi file have type/depend information, we can do type-check
when dynamic linking .o file.
First way is simpler, but you perhaps will lost state after reboot,
because you can't serialize state (such as FFI) sometimes.
Second way is more complicated, but you can present all state when hot-swapping.
Looks you need second way, from your code, that's wrong, you can't
dynamic link object file without type-check, and expect everything will
be fine.
If you don't type-check when linking code, it's very dangerous, it willl *crash* your
program once type mismatch or runtime error occur.
Infact, Don Stewart has implement a complete solution to dynamic
linking in Haskell program, at
http://hackage.haskell.org/package/plugins-1.4.1
Unfortunately, it's broken with ghc-6.12.x
Before Don fix plugins package, i recommend you read Don's new paper
(http://www.cse.unsw.edu.au/~dons/papers/dons-phd-thesis.pdf)
You will know every detail that how to dynamic extension Haskell
program.
Hope above will help you. :)
-- Andy
Hongmin Fan
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
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe