GHC for Plugins
Matt Walker
matt.g.d.walker at gmail.com
Tue Feb 13 21:50:10 UTC 2018
Hello,
I am developing a game and would like to write the core in haskell with
haskell also for scripting. I like haskell.
I have the following file to help me do this.
>>> BEGIN FILE
{-# LANGUAGE ScopedTypeVariables #-}
module Plugin.Load where
import Data.Functor
import System.Directory
import GHC
import GHC.Paths
import DynFlags
import Unsafe.Coerce
type ModName = String
type ValName = String
loadPlugin :: FilePath -> ModName -> ValName -> IO a
loadPlugin dir modName value = do
withCurrentDirectory dir $
defaultErrorHandler defaultFatalMessager defaultFlushOut $
runGhc (Just libdir) $ do
dynFlags <- getSessionDynFlags
setSessionDynFlags $ dynamicTooMkDynamicDynFlags $ dynFlags
{ importPaths = [modName] ++ importPaths dynFlags
, hscTarget = HscAsm
, ghcLink = LinkInMemory
, ghcMode = CompManager
}
sequence [guessTarget modName Nothing] >>= setTargets
load LoadAllTargets
setContext [IIDecl $ simpleImportDecl $ mkModuleName modName]
fetched <- compileExpr (modName ++ "." ++ value)
return (unsafeCoerce fetched :: a)
<<< END FILE
The problem is that if I run the function loadPlugin on the same input more
than once, GHC barfs. The error I get is:
/usr/bin/ld.gold: error: cannot find -lghc_5
collect2: error: ld returned 1 exit status
`gcc' failed in phase `Linker'. (Exit code: 1)
*** Exception: ExitFailure 1
sometimes it's -lghc_2 or -lghc_13 above. Anyways, it seems like I and/or
ghc isn't cleaning up properly after themself and then wants to try to
append numbers. Any idea what is causing this and how to fix it?
Thanks,
Matt
PS. is there a better way of doing this using Typeable? I'd rather not
unsafeCoerce.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/glasgow-haskell-users/attachments/20180213/b11a85c6/attachment.html>
More information about the Glasgow-haskell-users
mailing list