Skip to content

Instantly share code, notes, and snippets.

@jhartikainen
Created August 20, 2011 11:31
Show Gist options
  • Star 6 You must be signed in to star a gist
  • Fork 2 You must be signed in to fork a gist
  • Save jhartikainen/1158986 to your computer and use it in GitHub Desktop.
Save jhartikainen/1158986 to your computer and use it in GitHub Desktop.
Module for loading modules dynamically in Haskell
{-# LANGUAGE ScopedTypeVariables #-}
module DynLoad (
loadSourceGhc,
execFnGhc
) where
import Control.Exception (throw)
import GHC hiding (loadModule)
import GHC.Paths (libdir)
import HscTypes (SourceError, srcErrorMessages)
import DynFlags
import Unsafe.Coerce
import Bag (bagToList)
execFnGhc :: String -> String -> Ghc a
execFnGhc modname fn = do
mod <- findModule (mkModuleName modname) Nothing
setContext [] [mod]
value <- compileExpr (modname ++ "." ++ fn)
let value' = (unsafeCoerce value) :: a
return value'
loadSourceGhc :: String -> Ghc (Maybe String)
loadSourceGhc path = let
throwingLogger (Just e) = throw e
throwingLogger _ = return ()
in do
dflags <- getSessionDynFlags
setSessionDynFlags (dflags{
ghcLink = LinkInMemory,
hscTarget = HscInterpreted,
packageFlags = [ExposePackage "ghc"]
})
target <- guessTarget path Nothing
addTarget target
r <- loadWithLogger throwingLogger LoadAllTargets
case r of
Failed -> return $ Just "Generic module load error"
Succeeded -> return Nothing
`gcatch` \(e :: SourceError) -> let
errors e = concat $ map show (bagToList $ srcErrorMessages e)
in
return $ Just (errors e)
@worldsayshi
Copy link

I made a fork to make it compile in 7.6.*

See here: https://gist.github.com/worldsayshi/8853946

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment