module Hint.Context (
isModuleInterpreted,
loadModules, getLoadedModules, setTopLevelModules,
setImports, setImportsQ, setImportsF,
reset,
PhantomModule(..),
cleanPhantomModules,
supportString, supportShow
) where
import Prelude hiding (mod)
import Data.Char
import Data.Either (partitionEithers)
import Data.List
import Control.Arrow ((***))
import Control.Monad (filterM, unless, guard, foldM)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Catch
import Hint.Base
import Hint.Conversions
import qualified Hint.CompatPlatform as Compat
import qualified Hint.GHC as GHC
import System.Random
import System.FilePath
import System.Directory
import Hint.Configuration (setGhcOption)
import System.IO.Temp
type ModuleText = String
newPhantomModule :: MonadInterpreter m => m PhantomModule
newPhantomModule :: forall (m :: * -> *). MonadInterpreter m => m PhantomModule
newPhantomModule =
do Int
n <- IO Int -> m Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Int
forall a (m :: * -> *). (Random a, MonadIO m) => m a
randomIO
Int
p <- IO Int -> m Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Int
Compat.getPID
([ModuleName]
ls,[ModuleName]
is) <- m ([ModuleName], [ModuleName])
forall (m :: * -> *).
MonadInterpreter m =>
m ([ModuleName], [ModuleName])
allModulesInContext
let nums :: ModuleName
nums = [ModuleName] -> ModuleName
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [Int -> ModuleName
forall a. Show a => a -> ModuleName
show (Int -> Int
forall a. Num a => a -> a
abs Int
n::Int), Int -> ModuleName
forall a. Show a => a -> ModuleName
show Int
p, (Char -> Bool) -> ModuleName -> ModuleName
forall a. (a -> Bool) -> [a] -> [a]
filter Char -> Bool
isDigit (ModuleName -> ModuleName) -> ModuleName -> ModuleName
forall a b. (a -> b) -> a -> b
$ [ModuleName] -> ModuleName
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([ModuleName]
ls [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ [ModuleName]
is)]
let mod_name :: ModuleName
mod_name = Char
'M'Char -> ModuleName -> ModuleName
forall a. a -> [a] -> [a]
:ModuleName
nums
ModuleName
tmp_dir <- m ModuleName
forall (m :: * -> *). MonadInterpreter m => m ModuleName
getPhantomDirectory
PhantomModule -> m PhantomModule
forall (m :: * -> *) a. Monad m => a -> m a
return PhantomModule :: ModuleName -> ModuleName -> PhantomModule
PhantomModule{pmName :: ModuleName
pmName = ModuleName
mod_name, pmFile :: ModuleName
pmFile = ModuleName
tmp_dir ModuleName -> ModuleName -> ModuleName
</> ModuleName
mod_name ModuleName -> ModuleName -> ModuleName
<.> ModuleName
"hs"}
getPhantomDirectory :: MonadInterpreter m => m FilePath
getPhantomDirectory :: forall (m :: * -> *). MonadInterpreter m => m ModuleName
getPhantomDirectory =
do Maybe ModuleName
mfp <- (InterpreterState -> Maybe ModuleName) -> m (Maybe ModuleName)
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> Maybe ModuleName
phantomDirectory
case Maybe ModuleName
mfp of
Just ModuleName
fp -> ModuleName -> m ModuleName
forall (m :: * -> *) a. Monad m => a -> m a
return ModuleName
fp
Maybe ModuleName
Nothing -> do ModuleName
tmp_dir <- IO ModuleName -> m ModuleName
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ModuleName
getTemporaryDirectory
ModuleName
fp <- IO ModuleName -> m ModuleName
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ModuleName -> m ModuleName) -> IO ModuleName -> m ModuleName
forall a b. (a -> b) -> a -> b
$ ModuleName -> ModuleName -> IO ModuleName
createTempDirectory ModuleName
tmp_dir ModuleName
"hint"
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{ phantomDirectory :: Maybe ModuleName
phantomDirectory = ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just ModuleName
fp })
ModuleName -> m ()
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m ()
setGhcOption (ModuleName -> m ()) -> ModuleName -> m ()
forall a b. (a -> b) -> a -> b
$ ModuleName
"-i" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
fp
ModuleName -> m ModuleName
forall (m :: * -> *) a. Monad m => a -> m a
return ModuleName
fp
allModulesInContext :: MonadInterpreter m => m ([ModuleName], [ModuleName])
allModulesInContext :: forall (m :: * -> *).
MonadInterpreter m =>
m ([ModuleName], [ModuleName])
allModulesInContext = RunGhc m ([ModuleName], [ModuleName])
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}.
(MonadIO n, MonadMask n) =>
GhcT n ([ModuleName], [ModuleName])
forall (m :: * -> *). GhcMonad m => m ([ModuleName], [ModuleName])
getContextNames
getContext :: GHC.GhcMonad m => m ([GHC.Module], [GHC.ImportDecl GHC.GhcPs])
getContext :: forall (m :: * -> *).
GhcMonad m =>
m ([Module], [ImportDecl GhcPs])
getContext = do
[InteractiveImport]
ctx <- m [InteractiveImport]
forall (m :: * -> *). GhcMonad m => m [InteractiveImport]
GHC.getContext
(([Module], [ImportDecl GhcPs])
-> InteractiveImport -> m ([Module], [ImportDecl GhcPs]))
-> ([Module], [ImportDecl GhcPs])
-> [InteractiveImport]
-> m ([Module], [ImportDecl GhcPs])
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM ([Module], [ImportDecl GhcPs])
-> InteractiveImport -> m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *).
GhcMonad m =>
([Module], [ImportDecl GhcPs])
-> InteractiveImport -> m ([Module], [ImportDecl GhcPs])
f ([], []) [InteractiveImport]
ctx
where
f :: (GHC.GhcMonad m) =>
([GHC.Module], [GHC.ImportDecl GHC.GhcPs]) ->
GHC.InteractiveImport ->
m ([GHC.Module], [GHC.ImportDecl GHC.GhcPs])
f :: forall (m :: * -> *).
GhcMonad m =>
([Module], [ImportDecl GhcPs])
-> InteractiveImport -> m ([Module], [ImportDecl GhcPs])
f ([Module]
ns, [ImportDecl GhcPs]
ds) InteractiveImport
i = case InteractiveImport
i of
(GHC.IIDecl ImportDecl GhcPs
d) -> ([Module], [ImportDecl GhcPs]) -> m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *) a. Monad m => a -> m a
return ([Module]
ns, ImportDecl GhcPs
d ImportDecl GhcPs -> [ImportDecl GhcPs] -> [ImportDecl GhcPs]
forall a. a -> [a] -> [a]
: [ImportDecl GhcPs]
ds)
(GHC.IIModule ModuleName
m) -> do Module
n <- ModuleName -> Maybe FastString -> m Module
forall (m :: * -> *).
GhcMonad m =>
ModuleName -> Maybe FastString -> m Module
GHC.findModule ModuleName
m Maybe FastString
forall a. Maybe a
Nothing; ([Module], [ImportDecl GhcPs]) -> m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *) a. Monad m => a -> m a
return (Module
n Module -> [Module] -> [Module]
forall a. a -> [a] -> [a]
: [Module]
ns, [ImportDecl GhcPs]
ds)
modToIIMod :: GHC.Module -> GHC.InteractiveImport
modToIIMod :: Module -> InteractiveImport
modToIIMod = ModuleName -> InteractiveImport
GHC.IIModule (ModuleName -> InteractiveImport)
-> (Module -> ModuleName) -> Module -> InteractiveImport
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> ModuleName
forall unit. GenModule unit -> ModuleName
GHC.moduleName
getContextNames :: GHC.GhcMonad m => m([String], [String])
getContextNames :: forall (m :: * -> *). GhcMonad m => m ([ModuleName], [ModuleName])
getContextNames = (([Module], [ImportDecl GhcPs]) -> ([ModuleName], [ModuleName]))
-> m ([Module], [ImportDecl GhcPs])
-> m ([ModuleName], [ModuleName])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Module -> ModuleName) -> [Module] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map Module -> ModuleName
forall {unit}. GenModule unit -> ModuleName
name ([Module] -> [ModuleName])
-> ([ImportDecl GhcPs] -> [ModuleName])
-> ([Module], [ImportDecl GhcPs])
-> ([ModuleName], [ModuleName])
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** (ImportDecl GhcPs -> ModuleName)
-> [ImportDecl GhcPs] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map ImportDecl GhcPs -> ModuleName
forall {pass}. ImportDecl pass -> ModuleName
decl) m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *).
GhcMonad m =>
m ([Module], [ImportDecl GhcPs])
getContext
where name :: GenModule unit -> ModuleName
name = ModuleName -> ModuleName
GHC.moduleNameString (ModuleName -> ModuleName)
-> (GenModule unit -> ModuleName) -> GenModule unit -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenModule unit -> ModuleName
forall unit. GenModule unit -> ModuleName
GHC.moduleName
decl :: ImportDecl pass -> ModuleName
decl = ModuleName -> ModuleName
GHC.moduleNameString (ModuleName -> ModuleName)
-> (ImportDecl pass -> ModuleName) -> ImportDecl pass -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenLocated SrcSpan ModuleName -> ModuleName
forall l e. GenLocated l e -> e
GHC.unLoc (GenLocated SrcSpan ModuleName -> ModuleName)
-> (ImportDecl pass -> GenLocated SrcSpan ModuleName)
-> ImportDecl pass
-> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ImportDecl pass -> GenLocated SrcSpan ModuleName
forall pass. ImportDecl pass -> GenLocated SrcSpan ModuleName
GHC.ideclName
setContext :: GHC.GhcMonad m => [GHC.Module] -> [GHC.ImportDecl GHC.GhcPs] -> m ()
setContext :: forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [Module]
ms [ImportDecl GhcPs]
ds =
let ms' :: [InteractiveImport]
ms' = (Module -> InteractiveImport) -> [Module] -> [InteractiveImport]
forall a b. (a -> b) -> [a] -> [b]
map Module -> InteractiveImport
modToIIMod [Module]
ms
ds' :: [InteractiveImport]
ds' = (ImportDecl GhcPs -> InteractiveImport)
-> [ImportDecl GhcPs] -> [InteractiveImport]
forall a b. (a -> b) -> [a] -> [b]
map ImportDecl GhcPs -> InteractiveImport
GHC.IIDecl [ImportDecl GhcPs]
ds
is :: [InteractiveImport]
is = [InteractiveImport]
ms' [InteractiveImport] -> [InteractiveImport] -> [InteractiveImport]
forall a. [a] -> [a] -> [a]
++ [InteractiveImport]
ds'
in [InteractiveImport] -> m ()
forall (m :: * -> *). GhcMonad m => [InteractiveImport] -> m ()
GHC.setContext [InteractiveImport]
is
setContextModules :: GHC.GhcMonad m => [GHC.Module] -> [GHC.Module] -> m ()
setContextModules :: forall (m :: * -> *). GhcMonad m => [Module] -> [Module] -> m ()
setContextModules [Module]
as = [Module] -> [ImportDecl GhcPs] -> m ()
forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [Module]
as ([ImportDecl GhcPs] -> m ())
-> ([Module] -> [ImportDecl GhcPs]) -> [Module] -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Module -> ImportDecl GhcPs) -> [Module] -> [ImportDecl GhcPs]
forall a b. (a -> b) -> [a] -> [b]
map (ModuleName -> ImportDecl GhcPs
forall (p :: Pass). ModuleName -> ImportDecl (GhcPass p)
GHC.simpleImportDecl (ModuleName -> ImportDecl GhcPs)
-> (Module -> ModuleName) -> Module -> ImportDecl GhcPs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> ModuleName
forall unit. GenModule unit -> ModuleName
GHC.moduleName)
addPhantomModule :: MonadInterpreter m
=> (ModuleName -> ModuleText)
-> m PhantomModule
addPhantomModule :: forall (m :: * -> *).
MonadInterpreter m =>
(ModuleName -> ModuleName) -> m PhantomModule
addPhantomModule ModuleName -> ModuleName
mod_text =
do PhantomModule
pm <- m PhantomModule
forall (m :: * -> *). MonadInterpreter m => m PhantomModule
newPhantomModule
DynFlags
df <- RunGhc m DynFlags
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}. (MonadIO n, MonadMask n) => GhcT n DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
GHC.getSessionDynFlags
let t :: Target
t = DynFlags -> ModuleName -> Target
GHC.fileTarget DynFlags
df (PhantomModule -> ModuleName
pmFile PhantomModule
pm)
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ModuleName -> ModuleName -> IO ()
writeFile (PhantomModule -> ModuleName
pmFile PhantomModule
pm) (ModuleName -> ModuleName
mod_text (ModuleName -> ModuleName) -> ModuleName -> ModuleName
forall a b. (a -> b) -> a -> b
$ PhantomModule -> ModuleName
pmName PhantomModule
pm)
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{activePhantoms :: [PhantomModule]
activePhantoms = PhantomModule
pmPhantomModule -> [PhantomModule] -> [PhantomModule]
forall a. a -> [a] -> [a]
:InterpreterState -> [PhantomModule]
activePhantoms InterpreterState
s})
m (Maybe ()) -> m ()
forall (m :: * -> *) a. MonadInterpreter m => m (Maybe a) -> m a
mayFail (do
([Module]
old_top, [ImportDecl GhcPs]
old_imps) <- RunGhc m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}.
(MonadIO n, MonadMask n) =>
GhcT n ([Module], [ImportDecl GhcPs])
forall (m :: * -> *).
GhcMonad m =>
m ([Module], [ImportDecl GhcPs])
getContext
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ Target -> GhcT n ()
forall (m :: * -> *). GhcMonad m => Target -> m ()
GHC.addTarget Target
t
SuccessFlag
res <- RunGhc m SuccessFlag
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m SuccessFlag -> RunGhc m SuccessFlag
forall a b. (a -> b) -> a -> b
$ LoadHowMuch -> GhcT n SuccessFlag
forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
GHC.load LoadHowMuch
GHC.LoadAllTargets
if SuccessFlag -> Bool
isSucceeded SuccessFlag
res
then do RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Module] -> [ImportDecl GhcPs] -> GhcT n ()
forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [Module]
old_top [ImportDecl GhcPs]
old_imps
Maybe () -> m (Maybe ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe () -> m (Maybe ())) -> Maybe () -> m (Maybe ())
forall a b. (a -> b) -> a -> b
$ () -> Maybe ()
forall a. a -> Maybe a
Just ()
else Maybe () -> m (Maybe ())
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ()
forall a. Maybe a
Nothing)
m () -> (InterpreterError -> m ()) -> m ()
forall (m :: * -> *) a.
MonadInterpreter m =>
m a -> (InterpreterError -> m a) -> m a
`catchIE` (\InterpreterError
err -> case InterpreterError
err of
WontCompile [GhcError]
_ -> do PhantomModule -> m ()
forall (m :: * -> *). MonadInterpreter m => PhantomModule -> m ()
removePhantomModule PhantomModule
pm
InterpreterError -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM InterpreterError
err
InterpreterError
_ -> InterpreterError -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM InterpreterError
err)
PhantomModule -> m PhantomModule
forall (m :: * -> *) a. Monad m => a -> m a
return PhantomModule
pm
removePhantomModule :: forall m. MonadInterpreter m => PhantomModule -> m ()
removePhantomModule :: forall (m :: * -> *). MonadInterpreter m => PhantomModule -> m ()
removePhantomModule PhantomModule
pm =
do
Bool
isLoaded <- ModuleName -> m Bool
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Bool
moduleIsLoaded (ModuleName -> m Bool) -> ModuleName -> m Bool
forall a b. (a -> b) -> a -> b
$ PhantomModule -> ModuleName
pmName PhantomModule
pm
Bool
safeToRemove <-
if Bool
isLoaded
then do
Module
mod <- ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule (PhantomModule -> ModuleName
pmName PhantomModule
pm)
([Module]
mods, [ImportDecl GhcPs]
imps) <- RunGhc m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}.
(MonadIO n, MonadMask n) =>
GhcT n ([Module], [ImportDecl GhcPs])
forall (m :: * -> *).
GhcMonad m =>
m ([Module], [ImportDecl GhcPs])
getContext
let mods' :: [Module]
mods' = (Module -> Bool) -> [Module] -> [Module]
forall a. (a -> Bool) -> [a] -> [a]
filter (Module
mod Module -> Module -> Bool
forall a. Eq a => a -> a -> Bool
/=) [Module]
mods
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Module] -> [ImportDecl GhcPs] -> GhcT n ()
forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [Module]
mods' [ImportDecl GhcPs]
imps
let isNotPhantom :: GHC.Module -> m Bool
isNotPhantom :: Module -> m Bool
isNotPhantom Module
mod' = do
Bool -> Bool
not (Bool -> Bool) -> m Bool -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ModuleName -> m Bool
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Bool
isPhantomModule (Module -> ModuleName
moduleToString Module
mod')
[Module] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Module] -> Bool) -> m [Module] -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Module -> m Bool) -> [Module] -> m [Module]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM Module -> m Bool
isNotPhantom [Module]
mods'
else Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
let file_name :: ModuleName
file_name = PhantomModule -> ModuleName
pmFile PhantomModule
pm
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ do DynFlags
df <- GhcT n DynFlags
forall (m :: * -> *). GhcMonad m => m DynFlags
GHC.getSessionDynFlags
TargetId -> GhcT n ()
forall (m :: * -> *). GhcMonad m => TargetId -> m ()
GHC.removeTarget (Target -> TargetId
GHC.targetId (Target -> TargetId) -> Target -> TargetId
forall a b. (a -> b) -> a -> b
$ DynFlags -> ModuleName -> Target
GHC.fileTarget DynFlags
df ModuleName
file_name)
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{activePhantoms :: [PhantomModule]
activePhantoms = (PhantomModule -> Bool) -> [PhantomModule] -> [PhantomModule]
forall a. (a -> Bool) -> [a] -> [a]
filter (PhantomModule
pm PhantomModule -> PhantomModule -> Bool
forall a. Eq a => a -> a -> Bool
/=) ([PhantomModule] -> [PhantomModule])
-> [PhantomModule] -> [PhantomModule]
forall a b. (a -> b) -> a -> b
$ InterpreterState -> [PhantomModule]
activePhantoms InterpreterState
s})
if Bool
safeToRemove
then m (Maybe ()) -> m ()
forall (m :: * -> *) a. MonadInterpreter m => m (Maybe a) -> m a
mayFail (m (Maybe ()) -> m ()) -> m (Maybe ()) -> m ()
forall a b. (a -> b) -> a -> b
$ do SuccessFlag
res <- RunGhc m SuccessFlag
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m SuccessFlag -> RunGhc m SuccessFlag
forall a b. (a -> b) -> a -> b
$ LoadHowMuch -> GhcT n SuccessFlag
forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
GHC.load LoadHowMuch
GHC.LoadAllTargets
Maybe () -> m (Maybe ())
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe () -> m (Maybe ())) -> Maybe () -> m (Maybe ())
forall a b. (a -> b) -> a -> b
$ Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (SuccessFlag -> Bool
isSucceeded SuccessFlag
res) Maybe () -> Maybe () -> Maybe ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> Maybe ()
forall a. a -> Maybe a
Just ()
m (Maybe ()) -> m () -> m (Maybe ())
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
`finally` do IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ ModuleName -> IO ()
removeFile (PhantomModule -> ModuleName
pmFile PhantomModule
pm)
else (InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{zombiePhantoms :: [PhantomModule]
zombiePhantoms = PhantomModule
pmPhantomModule -> [PhantomModule] -> [PhantomModule]
forall a. a -> [a] -> [a]
:InterpreterState -> [PhantomModule]
zombiePhantoms InterpreterState
s})
getPhantomModules :: MonadInterpreter m => m ([PhantomModule], [PhantomModule])
getPhantomModules :: forall (m :: * -> *).
MonadInterpreter m =>
m ([PhantomModule], [PhantomModule])
getPhantomModules = do [PhantomModule]
active <- (InterpreterState -> [PhantomModule]) -> m [PhantomModule]
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> [PhantomModule]
activePhantoms
[PhantomModule]
zombie <- (InterpreterState -> [PhantomModule]) -> m [PhantomModule]
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> [PhantomModule]
zombiePhantoms
([PhantomModule], [PhantomModule])
-> m ([PhantomModule], [PhantomModule])
forall (m :: * -> *) a. Monad m => a -> m a
return ([PhantomModule]
active, [PhantomModule]
zombie)
isPhantomModule :: MonadInterpreter m => ModuleName -> m Bool
isPhantomModule :: forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Bool
isPhantomModule ModuleName
mn = do ([PhantomModule]
as,[PhantomModule]
zs) <- m ([PhantomModule], [PhantomModule])
forall (m :: * -> *).
MonadInterpreter m =>
m ([PhantomModule], [PhantomModule])
getPhantomModules
Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> m Bool) -> Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ ModuleName
mn ModuleName -> [ModuleName] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (PhantomModule -> ModuleName) -> [PhantomModule] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map PhantomModule -> ModuleName
pmName ([PhantomModule]
as [PhantomModule] -> [PhantomModule] -> [PhantomModule]
forall a. [a] -> [a] -> [a]
++ [PhantomModule]
zs)
loadModules :: MonadInterpreter m => [String] -> m ()
loadModules :: forall (m :: * -> *). MonadInterpreter m => [ModuleName] -> m ()
loadModules [ModuleName]
fs = do
m ()
forall (m :: * -> *). MonadInterpreter m => m ()
reset
[ModuleName] -> m ()
forall (m :: * -> *). MonadInterpreter m => [ModuleName] -> m ()
doLoad [ModuleName]
fs m () -> (InterpreterError -> m ()) -> m ()
forall (m :: * -> *) a.
MonadInterpreter m =>
m a -> (InterpreterError -> m a) -> m a
`catchIE` (\InterpreterError
e -> m ()
forall (m :: * -> *). MonadInterpreter m => m ()
reset m () -> m () -> m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> InterpreterError -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM InterpreterError
e)
doLoad :: MonadInterpreter m => [String] -> m ()
doLoad :: forall (m :: * -> *). MonadInterpreter m => [ModuleName] -> m ()
doLoad [ModuleName]
fs = do [Target]
targets <- (ModuleName -> m Target) -> [ModuleName] -> m [Target]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\ModuleName
f->RunGhc m Target
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m Target -> RunGhc m Target
forall a b. (a -> b) -> a -> b
$ ModuleName -> Maybe Phase -> GhcT n Target
forall (m :: * -> *).
GhcMonad m =>
ModuleName -> Maybe Phase -> m Target
GHC.guessTarget ModuleName
f Maybe Phase
forall a. Maybe a
Nothing) [ModuleName]
fs
[Target] -> MonadInterpreter m => m ()
forall (m :: * -> *). [Target] -> MonadInterpreter m => m ()
reinstallSupportModule [Target]
targets
isModuleInterpreted :: MonadInterpreter m => ModuleName -> m Bool
isModuleInterpreted :: forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Bool
isModuleInterpreted ModuleName
moduleName = do
Module
mod <- ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule ModuleName
moduleName
RunGhc m Bool
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m Bool -> RunGhc m Bool
forall a b. (a -> b) -> a -> b
$ Module -> GhcT n Bool
forall (m :: * -> *). GhcMonad m => Module -> m Bool
GHC.moduleIsInterpreted Module
mod
getLoadedModules :: MonadInterpreter m => m [ModuleName]
getLoadedModules :: forall (m :: * -> *). MonadInterpreter m => m [ModuleName]
getLoadedModules = do ([PhantomModule]
active_pms, [PhantomModule]
zombie_pms) <- m ([PhantomModule], [PhantomModule])
forall (m :: * -> *).
MonadInterpreter m =>
m ([PhantomModule], [PhantomModule])
getPhantomModules
[ModuleName]
ms <- (ModSummary -> ModuleName) -> [ModSummary] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map ModSummary -> ModuleName
modNameFromSummary ([ModSummary] -> [ModuleName]) -> m [ModSummary] -> m [ModuleName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m [ModSummary]
forall (m :: * -> *). MonadInterpreter m => m [ModSummary]
getLoadedModSummaries
[ModuleName] -> m [ModuleName]
forall (m :: * -> *) a. Monad m => a -> m a
return ([ModuleName] -> m [ModuleName]) -> [ModuleName] -> m [ModuleName]
forall a b. (a -> b) -> a -> b
$ [ModuleName]
ms [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a] -> [a]
\\ (PhantomModule -> ModuleName) -> [PhantomModule] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map PhantomModule -> ModuleName
pmName ([PhantomModule]
active_pms [PhantomModule] -> [PhantomModule] -> [PhantomModule]
forall a. [a] -> [a] -> [a]
++ [PhantomModule]
zombie_pms)
modNameFromSummary :: GHC.ModSummary -> ModuleName
modNameFromSummary :: ModSummary -> ModuleName
modNameFromSummary = Module -> ModuleName
moduleToString (Module -> ModuleName)
-> (ModSummary -> Module) -> ModSummary -> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModSummary -> Module
GHC.ms_mod
getLoadedModSummaries :: MonadInterpreter m => m [GHC.ModSummary]
getLoadedModSummaries :: forall (m :: * -> *). MonadInterpreter m => m [ModSummary]
getLoadedModSummaries = do
ModuleGraph
modGraph <- RunGhc m ModuleGraph
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}.
(MonadIO n, MonadMask n) =>
GhcT n ModuleGraph
forall (m :: * -> *). GhcMonad m => m ModuleGraph
GHC.getModuleGraph
let modSummaries :: [ModSummary]
modSummaries = ModuleGraph -> [ModSummary]
GHC.mgModSummaries ModuleGraph
modGraph
(ModSummary -> m Bool) -> [ModSummary] -> m [ModSummary]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (\ModSummary
modl -> RunGhc m Bool
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m Bool -> RunGhc m Bool
forall a b. (a -> b) -> a -> b
$ ModuleName -> GhcT n Bool
forall (m :: * -> *). GhcMonad m => ModuleName -> m Bool
GHC.isLoaded (ModuleName -> GhcT n Bool) -> ModuleName -> GhcT n Bool
forall a b. (a -> b) -> a -> b
$ ModSummary -> ModuleName
GHC.ms_mod_name ModSummary
modl) [ModSummary]
modSummaries
setTopLevelModules :: MonadInterpreter m => [ModuleName] -> m ()
setTopLevelModules :: forall (m :: * -> *). MonadInterpreter m => [ModuleName] -> m ()
setTopLevelModules [ModuleName]
ms =
do [ModSummary]
loaded_mods_ghc <- m [ModSummary]
forall (m :: * -> *). MonadInterpreter m => m [ModSummary]
getLoadedModSummaries
let not_loaded :: [ModuleName]
not_loaded = [ModuleName]
ms [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a] -> [a]
\\ (ModSummary -> ModuleName) -> [ModSummary] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map ModSummary -> ModuleName
modNameFromSummary [ModSummary]
loaded_mods_ghc
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([ModuleName] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModuleName]
not_loaded) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
InterpreterError -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (InterpreterError -> m ()) -> InterpreterError -> m ()
forall a b. (a -> b) -> a -> b
$ ModuleName -> InterpreterError
NotAllowed (ModuleName
"These modules have not been loaded:\n" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++
[ModuleName] -> ModuleName
unlines [ModuleName]
not_loaded)
[PhantomModule]
active_pms <- (InterpreterState -> [PhantomModule]) -> m [PhantomModule]
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> [PhantomModule]
activePhantoms
[Module]
ms_mods <- (ModuleName -> m Module) -> [ModuleName] -> m [Module]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule ([ModuleName] -> [ModuleName]
forall a. Eq a => [a] -> [a]
nub ([ModuleName] -> [ModuleName]) -> [ModuleName] -> [ModuleName]
forall a b. (a -> b) -> a -> b
$ [ModuleName]
ms [ModuleName] -> [ModuleName] -> [ModuleName]
forall a. [a] -> [a] -> [a]
++ (PhantomModule -> ModuleName) -> [PhantomModule] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map PhantomModule -> ModuleName
pmName [PhantomModule]
active_pms)
let mod_is_interpr :: Module -> m Bool
mod_is_interpr Module
modl = RunGhc m Bool
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m Bool -> RunGhc m Bool
forall a b. (a -> b) -> a -> b
$ Module -> GhcT n Bool
forall (m :: * -> *). GhcMonad m => Module -> m Bool
GHC.moduleIsInterpreted Module
modl
[Module]
not_interpreted <- (Module -> m Bool) -> [Module] -> m [Module]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM ((Bool -> Bool) -> m Bool -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Bool
not (m Bool -> m Bool) -> (Module -> m Bool) -> Module -> m Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Module -> m Bool
forall {m :: * -> *}. MonadInterpreter m => Module -> m Bool
mod_is_interpr) [Module]
ms_mods
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([Module] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Module]
not_interpreted) (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$
InterpreterError -> m ()
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (InterpreterError -> m ()) -> InterpreterError -> m ()
forall a b. (a -> b) -> a -> b
$ ModuleName -> InterpreterError
NotAllowed (ModuleName
"These modules are not interpreted:\n" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++
[ModuleName] -> ModuleName
unlines ((Module -> ModuleName) -> [Module] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map Module -> ModuleName
moduleToString [Module]
not_interpreted))
([Module]
_, [ImportDecl GhcPs]
old_imports) <- RunGhc m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}.
(MonadIO n, MonadMask n) =>
GhcT n ([Module], [ImportDecl GhcPs])
forall (m :: * -> *).
GhcMonad m =>
m ([Module], [ImportDecl GhcPs])
getContext
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Module] -> [ImportDecl GhcPs] -> GhcT n ()
forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [Module]
ms_mods [ImportDecl GhcPs]
old_imports
setImports :: MonadInterpreter m => [ModuleName] -> m ()
setImports :: forall (m :: * -> *). MonadInterpreter m => [ModuleName] -> m ()
setImports [ModuleName]
ms = [ModuleImport] -> m ()
forall (m :: * -> *). MonadInterpreter m => [ModuleImport] -> m ()
setImportsF ([ModuleImport] -> m ()) -> [ModuleImport] -> m ()
forall a b. (a -> b) -> a -> b
$ (ModuleName -> ModuleImport) -> [ModuleName] -> [ModuleImport]
forall a b. (a -> b) -> [a] -> [b]
map (\ModuleName
m -> ModuleName -> ModuleQualification -> ImportList -> ModuleImport
ModuleImport ModuleName
m ModuleQualification
NotQualified ImportList
NoImportList) [ModuleName]
ms
setImportsQ :: MonadInterpreter m => [(ModuleName, Maybe String)] -> m ()
setImportsQ :: forall (m :: * -> *).
MonadInterpreter m =>
[(ModuleName, Maybe ModuleName)] -> m ()
setImportsQ [(ModuleName, Maybe ModuleName)]
ms = [ModuleImport] -> m ()
forall (m :: * -> *). MonadInterpreter m => [ModuleImport] -> m ()
setImportsF ([ModuleImport] -> m ()) -> [ModuleImport] -> m ()
forall a b. (a -> b) -> a -> b
$ ((ModuleName, Maybe ModuleName) -> ModuleImport)
-> [(ModuleName, Maybe ModuleName)] -> [ModuleImport]
forall a b. (a -> b) -> [a] -> [b]
map (\(ModuleName
m,Maybe ModuleName
q) -> ModuleName -> ModuleQualification -> ImportList -> ModuleImport
ModuleImport ModuleName
m (ModuleQualification
-> (ModuleName -> ModuleQualification)
-> Maybe ModuleName
-> ModuleQualification
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ModuleQualification
NotQualified (Maybe ModuleName -> ModuleQualification
QualifiedAs (Maybe ModuleName -> ModuleQualification)
-> (ModuleName -> Maybe ModuleName)
-> ModuleName
-> ModuleQualification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just) Maybe ModuleName
q) ImportList
NoImportList) [(ModuleName, Maybe ModuleName)]
ms
setImportsF :: MonadInterpreter m => [ModuleImport] -> m ()
setImportsF :: forall (m :: * -> *). MonadInterpreter m => [ModuleImport] -> m ()
setImportsF [ModuleImport]
moduleImports = do
[Module]
regularMods <- (ModuleImport -> m Module) -> [ModuleImport] -> m [Module]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule (ModuleName -> m Module)
-> (ModuleImport -> ModuleName) -> ModuleImport -> m Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleImport -> ModuleName
modName) [ModuleImport]
regularImports
(ModuleImport -> m Module) -> [ModuleImport] -> m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule (ModuleName -> m Module)
-> (ModuleImport -> ModuleName) -> ModuleImport -> m Module
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleImport -> ModuleName
modName) [ModuleImport]
phantomImports
Maybe PhantomModule
old_qual_hack_mod <- (InterpreterState -> Maybe PhantomModule)
-> m (Maybe PhantomModule)
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> Maybe PhantomModule
importQualHackMod
m () -> (PhantomModule -> m ()) -> Maybe PhantomModule -> m ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) PhantomModule -> m ()
forall (m :: * -> *). MonadInterpreter m => PhantomModule -> m ()
removePhantomModule Maybe PhantomModule
old_qual_hack_mod
Maybe PhantomModule
maybe_phantom_module <- do
if [ModuleImport] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ModuleImport]
phantomImports
then Maybe PhantomModule -> m (Maybe PhantomModule)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PhantomModule
forall a. Maybe a
Nothing
else do
let moduleContents :: [ModuleName]
moduleContents = (ModuleImport -> ModuleName) -> [ModuleImport] -> [ModuleName]
forall a b. (a -> b) -> [a] -> [b]
map ModuleImport -> ModuleName
newImportLine [ModuleImport]
phantomImports
PhantomModule
new_phantom_module <- (ModuleName -> ModuleName) -> m PhantomModule
forall (m :: * -> *).
MonadInterpreter m =>
(ModuleName -> ModuleName) -> m PhantomModule
addPhantomModule ((ModuleName -> ModuleName) -> m PhantomModule)
-> (ModuleName -> ModuleName) -> m PhantomModule
forall a b. (a -> b) -> a -> b
$ \ModuleName
mod_name
-> [ModuleName] -> ModuleName
unlines ([ModuleName] -> ModuleName) -> [ModuleName] -> ModuleName
forall a b. (a -> b) -> a -> b
$ (ModuleName
"module " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
mod_name ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" where ")
ModuleName -> [ModuleName] -> [ModuleName]
forall a. a -> [a] -> [a]
: [ModuleName]
moduleContents
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{importQualHackMod :: Maybe PhantomModule
importQualHackMod = PhantomModule -> Maybe PhantomModule
forall a. a -> Maybe a
Just PhantomModule
new_phantom_module})
Maybe PhantomModule -> m (Maybe PhantomModule)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe PhantomModule -> m (Maybe PhantomModule))
-> Maybe PhantomModule -> m (Maybe PhantomModule)
forall a b. (a -> b) -> a -> b
$ PhantomModule -> Maybe PhantomModule
forall a. a -> Maybe a
Just PhantomModule
new_phantom_module
[Module]
phantom_mods <- case Maybe PhantomModule
maybe_phantom_module of
Maybe PhantomModule
Nothing -> do
[Module] -> m [Module]
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
Just PhantomModule
phantom_module-> do
Module
phantom_mod <- ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule (PhantomModule -> ModuleName
pmName PhantomModule
phantom_module)
[Module] -> m [Module]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Module
phantom_mod]
([Module]
old_top_level, [ImportDecl GhcPs]
_) <- RunGhc m ([Module], [ImportDecl GhcPs])
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc forall {n :: * -> *}.
(MonadIO n, MonadMask n) =>
GhcT n ([Module], [ImportDecl GhcPs])
forall (m :: * -> *).
GhcMonad m =>
m ([Module], [ImportDecl GhcPs])
getContext
let new_top_level :: [Module]
new_top_level = [Module]
phantom_mods [Module] -> [Module] -> [Module]
forall a. [a] -> [a] -> [a]
++ [Module]
old_top_level
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Module] -> [Module] -> GhcT n ()
forall (m :: * -> *). GhcMonad m => [Module] -> [Module] -> m ()
setContextModules [Module]
new_top_level [Module]
regularMods
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s ->InterpreterState
s{qualImports :: [ModuleImport]
qualImports = [ModuleImport]
phantomImports})
where
([ModuleImport]
regularImports, [ModuleImport]
phantomImports) = [Either ModuleImport ModuleImport]
-> ([ModuleImport], [ModuleImport])
forall a b. [Either a b] -> ([a], [b])
partitionEithers
([Either ModuleImport ModuleImport]
-> ([ModuleImport], [ModuleImport]))
-> [Either ModuleImport ModuleImport]
-> ([ModuleImport], [ModuleImport])
forall a b. (a -> b) -> a -> b
$ (ModuleImport -> Either ModuleImport ModuleImport)
-> [ModuleImport] -> [Either ModuleImport ModuleImport]
forall a b. (a -> b) -> [a] -> [b]
map (\ModuleImport
m -> if ModuleImport -> Bool
isQualified ModuleImport
m Bool -> Bool -> Bool
|| ModuleImport -> Bool
hasImportList ModuleImport
m
then ModuleImport -> Either ModuleImport ModuleImport
forall a b. b -> Either a b
Right ModuleImport
m
else ModuleImport -> Either ModuleImport ModuleImport
forall a b. a -> Either a b
Left ModuleImport
m)
[ModuleImport]
moduleImports
isQualified :: ModuleImport -> Bool
isQualified ModuleImport
m = ModuleImport -> ModuleQualification
modQual ModuleImport
m ModuleQualification -> ModuleQualification -> Bool
forall a. Eq a => a -> a -> Bool
/= ModuleQualification
NotQualified
hasImportList :: ModuleImport -> Bool
hasImportList ModuleImport
m = ModuleImport -> ImportList
modImp ModuleImport
m ImportList -> ImportList -> Bool
forall a. Eq a => a -> a -> Bool
/= ImportList
NoImportList
newImportLine :: ModuleImport -> ModuleName
newImportLine ModuleImport
m = [ModuleName] -> ModuleName
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ModuleName
"import ", case ModuleImport -> ModuleQualification
modQual ModuleImport
m of
ModuleQualification
NotQualified -> ModuleImport -> ModuleName
modName ModuleImport
m
ImportAs ModuleName
q -> ModuleImport -> ModuleName
modName ModuleImport
m ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" as " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
q
QualifiedAs Maybe ModuleName
Nothing -> ModuleName
"qualified " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleImport -> ModuleName
modName ModuleImport
m
QualifiedAs (Just ModuleName
q) -> ModuleName
"qualified " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleImport -> ModuleName
modName ModuleImport
m ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" as " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
q
,case ModuleImport -> ImportList
modImp ModuleImport
m of
ImportList
NoImportList -> ModuleName
""
ImportList [ModuleName]
l -> ModuleName
" (" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName -> [ModuleName] -> ModuleName
forall a. [a] -> [[a]] -> [a]
intercalate ModuleName
"," [ModuleName]
l ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
")"
HidingList [ModuleName]
l -> ModuleName
" hiding (" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName -> [ModuleName] -> ModuleName
forall a. [a] -> [[a]] -> [a]
intercalate ModuleName
"," [ModuleName]
l ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
")"
]
cleanPhantomModules :: MonadInterpreter m => m ()
cleanPhantomModules :: forall (m :: * -> *). MonadInterpreter m => m ()
cleanPhantomModules =
do
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Module] -> [ImportDecl GhcPs] -> GhcT n ()
forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [] []
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Target] -> GhcT n ()
forall (m :: * -> *). GhcMonad m => [Target] -> m ()
GHC.setTargets []
SuccessFlag
_ <- RunGhc m SuccessFlag
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m SuccessFlag -> RunGhc m SuccessFlag
forall a b. (a -> b) -> a -> b
$ LoadHowMuch -> GhcT n SuccessFlag
forall (m :: * -> *). GhcMonad m => LoadHowMuch -> m SuccessFlag
GHC.load LoadHowMuch
GHC.LoadAllTargets
[PhantomModule]
old_active <- (InterpreterState -> [PhantomModule]) -> m [PhantomModule]
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> [PhantomModule]
activePhantoms
[PhantomModule]
old_zombie <- (InterpreterState -> [PhantomModule]) -> m [PhantomModule]
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> [PhantomModule]
zombiePhantoms
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{activePhantoms :: [PhantomModule]
activePhantoms = [],
zombiePhantoms :: [PhantomModule]
zombiePhantoms = [],
importQualHackMod :: Maybe PhantomModule
importQualHackMod = Maybe PhantomModule
forall a. Maybe a
Nothing,
qualImports :: [ModuleImport]
qualImports = []})
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ (PhantomModule -> IO ()) -> [PhantomModule] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (ModuleName -> IO ()
removeFile (ModuleName -> IO ())
-> (PhantomModule -> ModuleName) -> PhantomModule -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhantomModule -> ModuleName
pmFile) ([PhantomModule]
old_active [PhantomModule] -> [PhantomModule] -> [PhantomModule]
forall a. [a] -> [a] -> [a]
++ [PhantomModule]
old_zombie)
Maybe ModuleName
old_phantomdir <- (InterpreterState -> Maybe ModuleName) -> m (Maybe ModuleName)
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> Maybe ModuleName
phantomDirectory
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
s -> InterpreterState
s{phantomDirectory :: Maybe ModuleName
phantomDirectory = Maybe ModuleName
forall a. Maybe a
Nothing})
IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do IO () -> (ModuleName -> IO ()) -> Maybe ModuleName -> IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) ModuleName -> IO ()
removeDirectory Maybe ModuleName
old_phantomdir
reset :: MonadInterpreter m => m ()
reset :: forall (m :: * -> *). MonadInterpreter m => m ()
reset = do
m ()
forall (m :: * -> *). MonadInterpreter m => m ()
cleanPhantomModules
[Target] -> m ()
forall (m :: * -> *). MonadInterpreter m => [Target] -> m ()
installSupportModule []
installSupportModule :: MonadInterpreter m => [GHC.Target] -> m ()
installSupportModule :: forall (m :: * -> *). MonadInterpreter m => [Target] -> m ()
installSupportModule [Target]
ts = do RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Target] -> GhcT n ()
forall (m :: * -> *). GhcMonad m => [Target] -> m ()
GHC.setTargets [Target]
ts
PhantomModule
mod <- (ModuleName -> ModuleName) -> m PhantomModule
forall (m :: * -> *).
MonadInterpreter m =>
(ModuleName -> ModuleName) -> m PhantomModule
addPhantomModule ModuleName -> ModuleName
support_module
(InterpreterState -> InterpreterState) -> m ()
forall (m :: * -> *).
MonadInterpreter m =>
(InterpreterState -> InterpreterState) -> m ()
onState (\InterpreterState
st -> InterpreterState
st{hintSupportModule :: PhantomModule
hintSupportModule = PhantomModule
mod})
Module
mod' <- ModuleName -> m Module
forall (m :: * -> *). MonadInterpreter m => ModuleName -> m Module
findModule (PhantomModule -> ModuleName
pmName PhantomModule
mod)
RunGhc m ()
forall (m :: * -> *) a. MonadInterpreter m => RunGhc m a
runGhc RunGhc m () -> RunGhc m ()
forall a b. (a -> b) -> a -> b
$ [Module] -> [ImportDecl GhcPs] -> GhcT n ()
forall (m :: * -> *).
GhcMonad m =>
[Module] -> [ImportDecl GhcPs] -> m ()
setContext [Module
mod'] []
where support_module :: ModuleName -> ModuleName
support_module ModuleName
m = [ModuleName] -> ModuleName
unlines [
ModuleName
"module " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
m ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
"( ",
ModuleName
" " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_String ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
",",
ModuleName
" " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_show ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
")",
ModuleName
"where",
ModuleName
"",
ModuleName
"import qualified Prelude as " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_P ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" (String, Show(show))",
ModuleName
"",
ModuleName
"type " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_String ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" = " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_P ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
".String",
ModuleName
"",
ModuleName
_show ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" :: " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_P ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
".Show a => a -> " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_P ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
".String",
ModuleName
_show ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
" = " ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
_P ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
".show"
]
where _String :: ModuleName
_String = ModuleName -> ModuleName
altStringName ModuleName
m
_show :: ModuleName
_show = ModuleName -> ModuleName
altShowName ModuleName
m
_P :: ModuleName
_P = ModuleName -> ModuleName
altPreludeName ModuleName
m
reinstallSupportModule :: [GHC.Target] -> MonadInterpreter m => m ()
reinstallSupportModule :: forall (m :: * -> *). [Target] -> MonadInterpreter m => m ()
reinstallSupportModule [Target]
ts = do PhantomModule
pm <- (InterpreterState -> PhantomModule) -> m PhantomModule
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState InterpreterState -> PhantomModule
hintSupportModule
PhantomModule -> m ()
forall (m :: * -> *). MonadInterpreter m => PhantomModule -> m ()
removePhantomModule PhantomModule
pm
[Target] -> m ()
forall (m :: * -> *). MonadInterpreter m => [Target] -> m ()
installSupportModule [Target]
ts
altStringName :: ModuleName -> String
altStringName :: ModuleName -> ModuleName
altStringName ModuleName
mod_name = ModuleName
"String_" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
mod_name
altShowName :: ModuleName -> String
altShowName :: ModuleName -> ModuleName
altShowName ModuleName
mod_name = ModuleName
"show_" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
mod_name
altPreludeName :: ModuleName -> String
altPreludeName :: ModuleName -> ModuleName
altPreludeName ModuleName
mod_name = ModuleName
"Prelude_" ModuleName -> ModuleName -> ModuleName
forall a. [a] -> [a] -> [a]
++ ModuleName
mod_name
supportString :: MonadInterpreter m => m String
supportString :: forall (m :: * -> *). MonadInterpreter m => m ModuleName
supportString = do ModuleName
mod_name <- (InterpreterState -> ModuleName) -> m ModuleName
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState (PhantomModule -> ModuleName
pmName (PhantomModule -> ModuleName)
-> (InterpreterState -> PhantomModule)
-> InterpreterState
-> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpreterState -> PhantomModule
hintSupportModule)
ModuleName -> m ModuleName
forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleName -> m ModuleName) -> ModuleName -> m ModuleName
forall a b. (a -> b) -> a -> b
$ [ModuleName] -> ModuleName
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ModuleName
mod_name, ModuleName
".", ModuleName -> ModuleName
altStringName ModuleName
mod_name]
supportShow :: MonadInterpreter m => m String
supportShow :: forall (m :: * -> *). MonadInterpreter m => m ModuleName
supportShow = do ModuleName
mod_name <- (InterpreterState -> ModuleName) -> m ModuleName
forall (m :: * -> *) a.
MonadInterpreter m =>
(InterpreterState -> a) -> m a
fromState (PhantomModule -> ModuleName
pmName (PhantomModule -> ModuleName)
-> (InterpreterState -> PhantomModule)
-> InterpreterState
-> ModuleName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InterpreterState -> PhantomModule
hintSupportModule)
ModuleName -> m ModuleName
forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleName -> m ModuleName) -> ModuleName -> m ModuleName
forall a b. (a -> b) -> a -> b
$ [ModuleName] -> ModuleName
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ModuleName
mod_name, ModuleName
".", ModuleName -> ModuleName
altShowName ModuleName
mod_name]