Suppose I do something similar with the GHC API (6.12.3, linux, x86, 32 bit). The attachment g.hs is my program to get a value from the package (called watermelon-0.1), print it, wait for me to press return, (at this point I modify the source code of the package, rebuild, reinstall), then loop back to get a value from the package again... how should I refresh so I get the new value?
Or I am supposed to forget this and just bump the version number of the package?
I attach my program g.hs and the package tarball for watermelon-0.1.
import Control.Monad(forever,liftM) import GHC import Unsafe.Coerce(unsafeCoerce) import GHC.Paths(libdir) import DynFlags(defaultDynFlags) import Linker(getHValue,initDynLinker,linkPackages,showLinkerState) import Module(mainPackageId,stringToPackageId) import Name(nameOccName) import OccName(isValOcc,occNameString) import MonadUtils(liftIO) main = forever $ do e <- ghcheader (unsafepkgget "watermelon-0.1" "W" "wm") print (e :: Int) getLine ghcheader :: Ghc a -> IO a ghcheader body = runGhc (Just libdir) $ do f0 <- getSessionDynFlags let f = dfmod f0 defaultCleanupHandler f $ do todo <- setSessionDynFlags f f1 <- getSessionDynFlags liftIO (initDynLinker f1) body where dfmod f = f{ghcLink=LinkInMemory} unsafepkgget :: (GhcMonad m) => String -> String -> String -> m a unsafepkgget spkg smod sval = unsafeget (pkgmod spkg smod) sval pkgmod :: String -> String -> Module pkgmod spkg smod = mkModule (stringToPackageId spkg) (mkModuleName smod) unsafeget :: (GhcMonad m) => Module -> String -> m a unsafeget m v = do mi <- getModuleInfo m case mi of Nothing -> error ("unsafeget fails at " ++ mns) Just i -> do case filter (match v) (modInfoExports i) of [n] -> do h <- getSession liftIO $ do val <- unsafeCoerce `liftM` getHValue h n -- showLinkerState return val _ -> error ("unsafegetval cannot find value " ++ v ++ " in module " ++ mns) where mns = moduleNameString (moduleName m) match s n = let o = nameOccName n in isValOcc o && s == occNameString o
watermelon-0.1.tar.gz
Description: GNU Zip compressed data
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users