I am trying to load and execute module dynamically,
Below is my code
TestModule.hs
module TestModule
where
evaluate = "Hello !!!"
Invoke.hs
module Invoke
where
import GHC
import DynFlags
import GHC.Paths (libdir)
import Unsafe.Coerce (unsafeCoerce)
import Data.Dynamic
execFnGhc :: String -> String -> Ghc a
execFnGhc modname fn = do
mod <- findModule (mkModuleName modname) Nothing
--setContext [IIModule mod]
GHC.setContext [ GHC.IIDecl $ (GHC.simpleImportDecl . GHC.mkModuleName $ modname) {GHC.ideclQualified = True} ]
value <- compileExpr (modname ++ "." ++ fn)
let value' = (unsafeCoerce value) :: a
return value'
Main2.hs
import GHC.Paths (libdir)
import GHC
import Invoke
-- import TestModule
main :: IO ()
main = runGhc (Just libdir) $ do
str <- execFnGhc "TestModule" "evaluate"
return str
When I try to run the program it show me below error
[root#vps mypproj]# ./Main2
Main2: <command line>: module is not loaded: `TestModule' (./TestModule.hs)
Not sure what I am missing, Can someone please help me resolve this error
My thought would be the problem has something to do with your path,and that the program silently errors when it can't load "TestModule," then complains that the module is not loaded. Have you tried using execFnGhc with a module that is already loaded, and have you tried loading a module that is in GHC naturally, such as Text.Parsec, then executing something in it?
I'd test myself, but I don't see a GHC.Paths library anywhere :/.
I was reading the relevant GHC source code recently, and it looks like findModule doesn't work on local modules (TestModule.hs in your case) unless they've already been loaded. (It works on modules in remote packages, however.)
To do GHCi style dynamic loading of compiled modules, your best bet is to use addTarget and load. As was mentioned in the comments, you also need to initialize the session dynamic flags. Here is a working version of your code:
module Invoke
where
import GHC
import DynFlags
import GHC.Paths (libdir)
import Unsafe.Coerce (unsafeCoerce)
import Data.Dynamic
execFnGhc :: String -> String -> Ghc String
execFnGhc modname fn = do
dflags <- getDynFlags
setSessionDynFlags dflags
let target = Target (TargetModule (mkModuleName modname)) True Nothing
addTarget target
load (LoadUpTo (mkModuleName modname))
mod <- findModule (mkModuleName modname) Nothing
GHC.setContext [ GHC.IIDecl $ (GHC.simpleImportDecl . GHC.mkModuleName $ modname) {GHC.ideclQualified = True} ]
value <- compileExpr (modname ++ "." ++ fn)
let value' = (unsafeCoerce value) :: String
return value'
What are the parameters of Target? The first is the module name; the second is whether or not we should be allowed to load object code, or always interpret the module; the last is an optional string buffer which you could use to override the source code in the actual file (it's Nothing because we don't need this.)
How did I figure this out? I looked at the code that GHCi uses to implement this in the GHC source code, as well as the compiler/main/GHC.hs. I've found this is the most reliable way to figure out how to get the GHC API to do what you want.
Confusing? The GHC API was not so much designed as accreted...
Related
I am writing a tool for which I want a modular architecture. By that I mean that the users would be able to write down a list of the modules they want to be loaded at start-up and my tool would be loading the corresponding .o for me.
Here is the code I managed to write up until now:
module Core where
import Data.Monoid ((<>))
import Data.Text (pack, unpack)
import System.Directory (getHomeDirectory)
import System.Plugins.DynamicLoader
loadPlugins :: [Text] -> IO ()
loadPlugins plugins = do
home <- getHomeDirectory
-- addDLL "/home/tchoutri/.stack/programs/x86_64-linux/ghc-tinfo6-8.4.3/lib/ghc-8.4.3/base-4.11.1.0/libHSbase-4.11.1.0-ghc8.4.3.so"
let paths = fmap (\x -> (pack home) <> "/.local/lib/polynot/polynot-" <> x <> ".o") plugins
forM_ paths $ \path -> load path
where
load path = do
m <- loadModuleFromPath (unpack path) (Just $ unpack path)
resolveFunctions
loadFunction m "runPlugin"
The plugin I'm trying to load at this moment is very simple:
{-# LANGUAGE OverloadedStrings #-}
module Polynot.Plugin.Twitter where
runPlugin :: IO ()
runPlugin = putStrLn "[Twitter] 'sup"
It is compiled with stack ghc -- --make -dynamic -fPIC -O3 twitter.hs. It is then renamed polynot-twitter.o, in ~/.local/lib/polynot/.
The compilation goes well, and when I run stack exec -- polynot, I get this error:
polynot: user error (Unable to get qualified name from: /home/tchoutri/.local/lib/polynot/polynot-twitter.o)
A quick google search showed me that the only instances of this error appear in the source code. :/
Moreover, I use the git version of dynamic-loader.
(I may be mistaken about my choice for a modular architecture, I totally accept that. If you have a better approach I could use, you can totally comment on it :)
I wasn't able to duplicate your error. I get a Prelude.head: empty list exception instead.
However, my guess is that it has to do with the functions in dynamic-loader expecting to load modules from a hierarchical directory structure that matches the module hierarchy.
In a nutshell, if I store the plugin in:
~/.local/lib/polynot/Polynot/Plugin/Twitter.o
and use loadModule like so:
loadModule "Polynot.Plugin.Twitter"
(Just "/home/buhr/.local/lib/polynot") (Just "o")
then it works okay for me.
The Main.hs I used was the following:
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad (forM_)
import Data.Monoid ((<>))
import Data.Text (pack, unpack, Text)
import System.Directory (getHomeDirectory)
import System.Plugins.DynamicLoader
loadPlugins :: [Text] -> IO ()
loadPlugins plugins = do
home <- getHomeDirectory
let basedir = (pack home) <> "/.local/lib/polynot"
forM_ plugins (load basedir)
where
load dir plugin = do
m <- loadModule (unpack plugin) (Just $ unpack dir) (Just "o")
resolveFunctions
entry <- loadFunction m "runPlugin"
entry
main = do
putStrLn "starting!"
loadPlugins ["Polynot.Plugin.Twitter"]
putStrLn "done!"
I need to have something like
-- Main.hs
module Main where
main :: IO ()
main = do
<import Plugin>
print Plugin.computation
With a Plugin like
-- Plugin.hs
module Plugin where
computation :: Int
computation = 4
However, I need the plugin to be compiled alongside the main application. They need to be deployed together. Only the import (not the compilation) of the module should happen dynamically.
I found Dynamically loading compiled Haskell module - GHC 7.6 along the way and it works just fine with GHC 8.0.2 except for the fact that it requires the source file of the plugin to be in the current working directory when executing the application.
Edit (07.12.2017)
Is it possible to load a module from a String instead of a file using the GHC API? http://hackage.haskell.org/package/ghc-8.2.1/docs/GHC.html#t:Target suggests that it's possible, but the documentation has many holes and I can't find a way to actually do this. If this can be accomplished, I can use file-embed to include the plugin source file into the compiled binary.
Example:
module Main where
-- Dynamic loading of modules
import GHC
import GHC.Paths ( libdir )
import DynFlags
import Unsafe.Coerce
import Data.Time.Clock (getCurrentTime)
import StringBuffer
pluginModuleNameStr :: String
pluginModuleNameStr = "MyPlugin"
pluginSourceStr :: String
pluginSourceStr = unlines
[ "module MyPlugin where"
, "computation :: Int"
, "computation = 4"
]
pluginModuleName :: ModuleName
pluginModuleName = mkModuleName pluginModuleNameStr
pluginSource :: StringBuffer
pluginSource = stringToStringBuffer pluginSourceStr
main :: IO ()
main = do
currentTime <- getCurrentTime
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
result <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
let target = Target { targetId = TargetModule $ pluginModuleName
, targetAllowObjCode = True
, targetContents = Just ( pluginSource
, currentTime
)
}
setTargets [target]
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
setContext [IIDecl $ simpleImportDecl pluginModuleName]
result <- compileExpr ("MyPlugin.computation")
let result' = unsafeCoerce result :: Int
return result'
print result
This, however, results in
<command-line>: panic! (the 'impossible' happened)
(GHC version 8.0.2 for x86_64-apple-darwin):
module ‘MyPlugin’ is a package module
Edit (08.12.2017)
I can compile the "plugin" directly into the final binary by writing the source to a temp file and then loading it like in the linked post (Dynamically loading compiled Haskell module - GHC 7.6). However, this does not play well if the plugin imports packages from Hackage:
module Main where
import Control.Monad.IO.Class (liftIO)
import DynFlags
import GHC
import GHC.Paths (libdir)
import System.Directory (getTemporaryDirectory, removePathForcibly)
import Unsafe.Coerce (unsafeCoerce)
pluginModuleNameStr :: String
pluginModuleNameStr = "MyPlugin"
pluginSourceStr :: String
pluginSourceStr = unlines
[ "module MyPlugin where"
, "import Data.Aeson"
, "computation :: Int"
, "computation = 4"
]
writeTempFile :: IO FilePath
writeTempFile = do
dir <- getTemporaryDirectory
let file = dir ++ "/" ++ pluginModuleNameStr ++ ".hs"
writeFile file pluginSourceStr
return file
main :: IO ()
main = do
moduleFile <- writeTempFile
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
result <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
target <- guessTarget moduleFile Nothing
setTargets [target]
r <- load LoadAllTargets
liftIO $ removePathForcibly moduleFile
case r of
Failed -> error "Compilation failed"
Succeeded -> do
setContext [IIDecl $ simpleImportDecl $ mkModuleName pluginModuleNameStr]
result <- compileExpr "MyPlugin.computation"
let result' = unsafeCoerce result :: Int
return result'
print result
Is there a way to load packages when, for instance, MyPlugin contains the statement import Data.Aeson? If I add it to the plugin string, it fails with
/var/folders/t2/hp9y8x6s6rs7zg21hdzvhbf40000gn/T/MyPlugin.hs:2:1: error:
Failed to load interface for ‘Data.Aeson’
Perhaps you meant Data.Version (from base-4.9.1.0)
Use -v to see a list of the files searched for.
haskell-loader-exe: panic! (the 'impossible' happened)
(GHC version 8.0.2 for x86_64-apple-darwin):
Compilation failed
CallStack (from HasCallStack):
error, called at app/Main.hs:40:19 in main:Main
The reason for my request is database support: We use Persistent to access a database and the dynamic import is needed to support multiple databases (MySQL, PostgreSQL and SQLite) while still allowing the end user to only install one of the three database servers (with other words: not requiring the user to install all of them if they only use, for instance, PostgreSQL). The module that is database-specific should only be loaded when the user actually configures the main application to use that module.
If I don't import Database.Persist.MySQL, then the application does not require MySQL to be installed. Otherwise, the application fails with, for instance,
dyld: Library not loaded:
/usr/local/opt/mysql/lib/libmysqlclient.20.dylib
on macOS.
A file with a matching module name must exist by the looks of it - it doesn't seem to matter what the file's content is.
On Linux I can even make it be a symlink to /dev/null and things work but a symlink to itself doesn't.
I'm trying to dynamically compile and load Haskell modules using GHC API. I understand the API fluctuates quite a bit from on one version to another so I'm specifically talking about GHC 7.6.*.
I have tried running the same code on MacOS and Linux. In both cases the Plugin module compiles fine but gives the following error on load: Cannot add module Plugin to context: not interpreted
The problem is similar to the one in this where the module would only load if it was compiled in the same run of the host program.
-- Host.hs: compile with ghc-7.6.*
-- $ ghc -package ghc -package ghc-paths Host.hs
-- Needs Plugin.hs in the same directory.
module Main where
import GHC
import GHC.Paths ( libdir )
import DynFlags
import Unsafe.Coerce
main :: IO ()
main =
defaultErrorHandler defaultFatalMessager defaultFlushOut $ do
result <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
target <- guessTarget "Plugin.hs" Nothing
setTargets [target]
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
setContext [IIModule (mkModuleName "Plugin")]
result <- compileExpr ("Plugin.getInt")
let result' = unsafeCoerce result :: Int
return result'
print result
And the plugin:
-- Plugin.hs
module Plugin where
getInt :: Int
getInt = 33
The problem is that you're using IIModule. This indicates that you want to bring the module and everything in it, including non-exported stuff into the context. It's essentially the same as :load with an asterisk in GHCi. And as you've noticed, this only works with interpreted code since it let's you "look inside" the module.
But that's not what you need here. What you want is to load it as if you used :module or an import declaration, which works with compiled modules. For that, you use IIDecl which takes an import declaration which you can make with simpleImportDecl:
setContext [IIDecl $ simpleImportDecl (mkModuleName "Plugin")]
I have an existing Haskell function that uses the GHC API to dynamically load compiled code from a module. It is based on the code from the blog post Dynamic Compilation and Loading of Modules in Haskell.
The code works fine in GHC 7.0, but had to be slightly modified to compile in GHC 7.2, because the GHC API changed.
The code now throws a runtime error in GHC 7.2:
mkTopLevEnv: not a home module (module name):(function name)
The code is
evalfuncLoadFFI String moduleName,
String externalFuncName,
String internalFuncName = do
result <- liftIO $ defaultRunGhc $ do
dynflags <- GHC.getSessionDynFlags
_ <- GHC.setSessionDynFlags dynflags
m <- GHC.findModule (GHC.mkModuleName moduleName) Nothing
--------------------------------------------------------
-- The following code works fine in GHC 7.0.4:
--
-- GHC.setContext [] [(m, Nothing)]
--
-- This new code attempts to set context to the module,
-- but throws an error in GHC 7.2:
--
(_,oi) <- GHC.getContext
GHC.setContext [m] oi
--------------------------------------------------------
fetched <- GHC.compileExpr (moduleName ++ "." ++ externalFuncName)
return (Unsafe.Coerce.unsafeCoerce fetched :: [LispVal] -> IOThrowsError LispVal)
defineVar env internalFuncName (IOFunc result)
For reference, the full code is available online in FFI.hs (github.com).
Does anyone have any idea how to fix or work around this problem?
Also, could this be caused by the new Safe Haskell changes in GHC 7.2, or is it just due to modifications to the GHC API?
The current module context is reserved for modules that are currently being compiled, i.e. when you specify modules in the context, they must explicitly not be external.
Instead, you should specify the wanted module as an import, in the second argument of setContext. This can be done like so:
GHC.setContext []
-- import qualified Module
[ (GHC.simpleImportDecl . GHC.mkModuleName $ moduleName)
{ GHC.ideclQualified = True
}
-- -- import qualified Data.Dynamic
-- , (GHC.simpleImportDecl . GHC.mkModuleName $ "Data.Dynamic")
-- { GHC.ideclQualified = True
-- }
]
fetched <- GHC.compileExpr $ moduleName ++ "." ++ externalFuncName
return . unsafeCoerce $ fetched
-- or:
-- fetched <- GHC.dynCompileExpr $ moduleName ++ "." ++ externalFuncName
-- return . fromDynamic (error "Illegal type cast") $ fetched
PS: it might be a good idea to use GHC.dynCompileExpr instead, so that you can avoid the unsafeCoerce. You must add a qualified import for Data.Dynamic in the context for it to work, but a Data.Dynamic.Dynamic value is generally nicer to work with, since you can handle type errors more gracefully. I've added the code for that as comments in the above code.
Update
And here is the syntax for GHC 7.4.1:
GHC.setContext
-- import qualified Module
[ GHC.IIDecl $
(GHC.simpleImportDecl . GHC.mkModuleName $ moduleName)
{GHC.ideclQualified = True}
]
Try
GHC.setContext [] [(m,Nothing)]
(from another StackOverflow question)
I have a module Target, with a function Target.accessMe inside it. I compile this module in some way, then get rid of the source code.
Now, what series of arcane incantations must I do to make a different program dynamically import Target.accessMe? This program knows accessMe's type in advance. Also, consider the fact that the source code of Target is not available.
The plugins package manages to accomplish this, but seems to have serious issues with working on Windows. I've checked out plugins's source, but am having trouble understanding it.
I've tried using Hint, but can only find out how to evaluate code that I have the source for.
Thanks for any help!
The answer to this question has been given to me elsewhere. The GHC API is capable of doing this. Here are two functions, one of which compiles Target.hs, while the other accesses Target.accessMe (and doesn't require the source code of the Target module to be there anymore).
import GHC
import DynFlags
compile :: String -> IO SuccessFlag
compile name = defaultRunGhc $ do
dynflags <- getSessionDynFlags
let dynflags' = dynflags -- You can change various options here.
setSessionDynFlags dynflags'
-- (name) can be "Target.hs", "Target", etc.
target <- guessTarget name Nothing
addTarget target
load LoadAllTargets -- Runs something like "ghc --make".
That's a function that compiles a given module and returns whether compilation succeeded or not. It uses a defaultRunGhc helper function that is defined as:
import GHC.Paths (libdir)
defaultRunGhc :: Ghc a -> IO a
defaultRunGhc = defaultErrorHandler defaultDynFlags . runGhc (Just libdir)
And now a function for fetching a value from the compiled module. The module's source code need not be present at this point.
import Unsafe.Coerce (unsafeCoerce)
fetch :: String -> String -> IO Int -- Assumes we are fetching an Int value.
fetch name value = defaultRunGhc $ do
-- Again, you can change various options in dynflags here, as above.
dynflags <- getSessionDynFlags
let m = mkModule (thisPackage dynflags) (mkModuleName name)
setContext [] [(m, Nothing)] -- Use setContext [] [m] for GHC<7.
fetched <- compileExpr (name ++ "." ++ value) -- Fetching "Target.accessMe".
return (unsafeCoerce fetched :: Int)
And that's it!
The plugins package is problematic anyway. You might want to look at Hint instead.