module Hint.Context (
ModuleName,
loadModules, getLoadedModules, setTopLevelModules,
setImports,
reset
)
where
import Data.List
import Control.Monad.Error
import Hint.Base
import Hint.Conversions
import qualified GHC
loadModules :: [String] -> Interpreter ()
loadModules fs =
do
ghc_session <- fromSessionState ghcSession
reset
let doLoad = mayFail $ do
targets <- mapM (\f -> GHC.guessTarget f Nothing) fs
GHC.setTargets ghc_session targets
res <- GHC.load ghc_session GHC.LoadAllTargets
return $ guard (isSucceeded res) >> Just ()
doLoad `catchError` (\e -> reset >> throwError e)
return ()
getLoadedModules :: Interpreter [ModuleName]
getLoadedModules = liftM (map modNameFromSummary) getLoadedModSummaries
modNameFromSummary :: GHC.ModSummary -> ModuleName
modNameFromSummary = fromGhcRep_ . GHC.ms_mod
getLoadedModSummaries :: Interpreter [GHC.ModSummary]
getLoadedModSummaries =
do ghc_session <- fromSessionState ghcSession
all_mod_summ <- liftIO $ GHC.getModuleGraph ghc_session
filterM (liftIO . GHC.isLoaded ghc_session . GHC.ms_mod_name) all_mod_summ
setTopLevelModules :: [ModuleName] -> Interpreter ()
setTopLevelModules ms =
do
ghc_session <- fromSessionState ghcSession
loaded_mods_ghc <- getLoadedModSummaries
let not_loaded = ms \\ map modNameFromSummary loaded_mods_ghc
when (not . null $ not_loaded) $
throwError $ NotAllowed ("These modules have not been loaded:\n" ++
unlines not_loaded)
ms_mods <- mapM findModule ms
let mod_is_interpr = GHC.moduleIsInterpreted ghc_session
not_interpreted <- liftIO $ filterM (liftM not . mod_is_interpr) ms_mods
when (not . null $ not_interpreted) $
throwError $ NotAllowed ("These modules are not interpreted:\n" ++
unlines (map fromGhcRep_ not_interpreted))
liftIO $ do
(_, old_imports) <- GHC.getContext ghc_session
GHC.setContext ghc_session ms_mods old_imports
setImports :: [ModuleName] -> Interpreter ()
setImports ms =
do
ghc_session <- fromSessionState ghcSession
ms_mods <- mapM findModule ms
liftIO $ do
(old_top_level, _) <- GHC.getContext ghc_session
GHC.setContext ghc_session old_top_level ms_mods
reset :: Interpreter ()
reset =
do
ghc_session <- fromSessionState ghcSession
liftIO $ GHC.setContext ghc_session [] []
liftIO $ GHC.setTargets ghc_session []
liftIO $ GHC.load ghc_session GHC.LoadAllTargets
return ()