Fix session caching, #807

also:
- cleanup LightGhc
- make the new DynFlags to compare against in a clean HscEnv
This commit is contained in:
Daniel Gröber 2016-07-16 03:42:59 +02:00
parent 500166c819
commit 01e3b8e3d6
6 changed files with 95 additions and 57 deletions

View File

@ -135,7 +135,7 @@ loadSymbolDb = do
dumpSymbol :: IOish m => GhcModT m () dumpSymbol :: IOish m => GhcModT m ()
dumpSymbol = do dumpSymbol = do
ts <- liftIO getCurrentModTime ts <- liftIO getCurrentModTime
st <- runGmPkgGhc $ (liftIO . getGlobalSymbolTable) =<< G.getSession st <- runGmPkgGhc $ getGlobalSymbolTable
liftIO . LBS.putStr $ encode SymbolDb { liftIO . LBS.putStr $ encode SymbolDb {
sdTable = st sdTable = st
, sdTimestamp = ts , sdTimestamp = ts
@ -148,19 +148,20 @@ isOlderThan tCache files =
any (tCache <=) $ map tfTime files -- including equal just in case any (tCache <=) $ map tfTime files -- including equal just in case
-- | Browsing all functions in all system modules. -- | Browsing all functions in all system modules.
getGlobalSymbolTable :: HscEnv -> IO (Map Symbol (Set ModuleNameBS)) getGlobalSymbolTable :: (G.GhcMonad m, MonadIO m)
getGlobalSymbolTable hsc_env = => m (Map Symbol (Set ModuleNameBS))
foldM (extend hsc_env) M.empty $ listVisibleModules $ hsc_dflags hsc_env getGlobalSymbolTable =
foldM extend M.empty =<< (listVisibleModules <$> G.getSessionDynFlags)
extend :: HscEnv extend :: (G.GhcMonad m, MonadIO m)
-> Map Symbol (Set ModuleNameBS) => Map Symbol (Set ModuleNameBS)
-> Module -> Module
-> IO (Map Symbol (Set ModuleNameBS)) -> m (Map Symbol (Set ModuleNameBS))
extend hsc_env mm mdl = do extend mm mdl = do
eps <- readIORef $ hsc_EPS hsc_env hsc_env <- G.getSession
modinfo <- unsafeInterleaveIO $ runLightGhc hsc_env $ do eps <- liftIO $ readIORef $ hsc_EPS hsc_env
modinfo <- liftIO $ unsafeInterleaveIO $ runLightGhc hsc_env $ do
G.getModuleInfo mdl <* liftIO (writeIORef (hsc_EPS hsc_env) eps) G.getModuleInfo mdl <* liftIO (writeIORef (hsc_EPS hsc_env) eps)
return $ M.unionWith S.union mm $ extractBindings modinfo mdl return $ M.unionWith S.union mm $ extractBindings modinfo mdl
extractBindings :: Maybe G.ModuleInfo extractBindings :: Maybe G.ModuleInfo

View File

@ -47,6 +47,7 @@ module Language.Haskell.GhcMod.Gap (
, parseModuleHeader , parseModuleHeader
, mkErrStyle' , mkErrStyle'
, everythingStagedWithContext , everythingStagedWithContext
, withCleanupSession
) where ) where
import Control.Applicative hiding (empty) import Control.Applicative hiding (empty)
@ -72,6 +73,8 @@ import StringBuffer
import TcType import TcType
import Var (varType) import Var (varType)
import System.Directory import System.Directory
import SysTools
import GHCi (stopIServ)
import qualified Name import qualified Name
import qualified InstEnv import qualified InstEnv
@ -665,3 +668,20 @@ everythingStagedWithContext stage s0 f z q x
#endif #endif
fixity = const (stage<Renamer) :: GHC.Fixity -> Bool fixity = const (stage<Renamer) :: GHC.Fixity -> Bool
(r, s') = q x s0 (r, s') = q x s0
withCleanupSession :: GhcMonad m => m a -> m a
#if __GLASGOW_HASKELL__ >= 800
withCleanupSession ghc = ghc `gfinally` cleanup
where
cleanup = do
hsc_env <- getSession
let dflags = hsc_dflags hsc_env
liftIO $ do
cleanTempFiles dflags
cleanTempDirs dflags
stopIServ hsc_env
#else
withCleanupSession action = do
df <- getSessionDynFlags
GHC.defaultCleanupHandler df action
#endif

View File

@ -1,5 +1,6 @@
module Language.Haskell.GhcMod.LightGhc where module Language.Haskell.GhcMod.LightGhc where
import Control.Monad
import Control.Monad.Reader (runReaderT) import Control.Monad.Reader (runReaderT)
import Data.IORef import Data.IORef
@ -14,35 +15,46 @@ import HscTypes
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Monad.Types import Language.Haskell.GhcMod.Monad.Types
import Language.Haskell.GhcMod.DynFlags import Language.Haskell.GhcMod.DynFlags
import qualified Language.Haskell.GhcMod.Gap as Gap
withLightHscEnv :: forall m a. IOish m -- We have to be more careful about tearing down 'HscEnv's since GHC 8 added an
=> [GHCOption] -> (HscEnv -> m a) -> m a -- out of process GHCI server which has to be shutdown.
withLightHscEnv opts action = gbracket initEnv teardownEnv action newLightEnv :: IOish m => (DynFlags -> LightGhc DynFlags) -> m HscEnv
where newLightEnv mdf = do
teardownEnv :: HscEnv -> m () df <- liftIO $ do
teardownEnv env = liftIO $ do
let dflags = hsc_dflags env
cleanTempFiles dflags
cleanTempDirs dflags
initEnv :: m HscEnv
initEnv = liftIO $ do
initStaticOpts initStaticOpts
settings <- initSysTools (Just libdir) settings <- initSysTools (Just libdir)
dflags <- initDynFlags (defaultDynFlags settings) initDynFlags $ defaultDynFlags settings
env <- newHscEnv dflags
dflags' <- runLightGhc env $ do hsc_env <- liftIO $ newHscEnv df
df' <- runLightGhc hsc_env $ mdf df
return $ hsc_env {
hsc_dflags = df',
hsc_IC = (hsc_IC hsc_env) { ic_dflags = df' }
}
teardownLightEnv :: MonadIO m => HscEnv -> m ()
teardownLightEnv env = runLightGhc env $ do
Gap.withCleanupSession $ return ()
withLightHscEnv'
:: IOish m => (DynFlags -> LightGhc DynFlags) -> (HscEnv -> m a) -> m a
withLightHscEnv' mdf action = gbracket (newLightEnv mdf) teardownLightEnv action
withLightHscEnv :: IOish m => [GHCOption] -> (HscEnv -> m a) -> m a
withLightHscEnv opts = withLightHscEnv' (f <=< liftIO . newHscEnv)
where
f env = runLightGhc env $ do
-- HomeModuleGraph and probably all other clients get into all sorts of -- HomeModuleGraph and probably all other clients get into all sorts of
-- trouble if the package state isn't initialized here -- trouble if the package state isn't initialized here
_ <- setSessionDynFlags =<< addCmdOpts opts =<< getSessionDynFlags _ <- setSessionDynFlags =<< addCmdOpts opts =<< getSessionDynFlags
getSessionDynFlags getSessionDynFlags
newHscEnv dflags'
runLightGhc :: HscEnv -> LightGhc a -> IO a runLightGhc :: MonadIO m => HscEnv -> LightGhc a -> m a
runLightGhc env action = do runLightGhc env action = liftIO $ do
renv <- newIORef env renv <- newIORef env
flip runReaderT renv $ unLightGhc action flip runReaderT renv $ unLightGhc action
runLightGhc' :: IORef HscEnv -> LightGhc a -> IO a runLightGhc' :: MonadIO m => IORef HscEnv -> LightGhc a -> m a
runLightGhc' renv action = do runLightGhc' renv action = liftIO $ do
flip runReaderT renv $ unLightGhc action flip runReaderT renv $ unLightGhc action

View File

@ -27,6 +27,7 @@ import GHC.LanguageExtensions
import GHC.Paths (libdir) import GHC.Paths (libdir)
import SysTools import SysTools
import DynFlags import DynFlags
import HscTypes
import Language.Haskell.GhcMod.DynFlags import Language.Haskell.GhcMod.DynFlags
import Language.Haskell.GhcMod.Monad.Types import Language.Haskell.GhcMod.Monad.Types
@ -69,39 +70,44 @@ runGmPkgGhc action = do
withLightHscEnv pkgOpts $ \env -> liftIO $ runLightGhc env action withLightHscEnv pkgOpts $ \env -> liftIO $ runLightGhc env action
initSession :: IOish m initSession :: IOish m
=> [GHCOption] -> (forall gm. GhcMonad gm => DynFlags -> gm DynFlags) -> GhcModT m () => [GHCOption]
-> (forall gm. GhcMonad gm => DynFlags -> gm DynFlags)
-> GhcModT m ()
initSession opts mdf = do initSession opts mdf = do
s <- gmsGet s <- gmsGet
case gmGhcSession s of case gmGhcSession s of
Nothing -> do Nothing -> do
gmLog GmDebug "initSession" $ text "Session not initialized, creating new one" gmLog GmDebug "initSession" $ text "Session not initialized, creating new one"
putNewSession s putNewSession s
Just GmGhcSession {..} -> do Just (GmGhcSession hsc_env_ref) -> do
gmLog GmDebug "initSession" $ text "Flags changed, creating new session"
crdl <- cradle crdl <- cradle
changed <- liftIO $ runLightGhc' gmgsSession $ do
df <- getSessionDynFlags df <- liftIO $ hsc_dflags <$> readIORef hsc_env_ref
ndf <- initDF crdl changed <-
return $ ndf `eqDynFlags` df withLightHscEnv' (initDF crdl) $ \hsc_env ->
return $ not $ (hsc_dflags hsc_env) `eqDynFlags` df
if changed if changed
then putNewSession s then do
else return () gmLog GmDebug "initSession" $ text "Flags changed, creating new session"
teardownSession hsc_env_ref
putNewSession s
else
gmLog GmDebug "initSession" $ text "Session already initialized"
where where
initDF Cradle { cradleTempDir } = do initDF Cradle { cradleTempDir } df =
let setDf df = setTmpDir cradleTempDir <$> (mdf =<< addCmdOpts opts df) setTmpDir cradleTempDir <$> (mdf =<< addCmdOpts opts df)
_ <- setSessionDynFlags =<< setDf =<< getSessionDynFlags
getSessionDynFlags
teardownSession hsc_env_ref = do
hsc_env <- liftIO $ readIORef hsc_env_ref
teardownLightEnv hsc_env
putNewSession :: IOish m => GhcModState -> GhcModT m ()
putNewSession s = do putNewSession s = do
rghc <- (liftIO . newIORef =<< newSession)
gmsPut s { gmGhcSession = Just $ GmGhcSession opts rghc }
newSession = do
crdl <- cradle crdl <- cradle
liftIO $ runGhc (Just libdir) $ do nhsc_env_ref <- liftIO . newIORef =<< newLightEnv (initDF crdl)
_ <- initDF crdl runLightGhc' nhsc_env_ref $ setSessionDynFlags =<< getSessionDynFlags
getSession gmsPut s { gmGhcSession = Just $ GmGhcSession nhsc_env_ref }
-- | Drop the currently active GHC session, the next that requires a GHC session -- | Drop the currently active GHC session, the next that requires a GHC session
@ -110,7 +116,7 @@ dropSession :: IOish m => GhcModT m ()
dropSession = do dropSession = do
s <- gmsGet s <- gmsGet
case gmGhcSession s of case gmGhcSession s of
Just (GmGhcSession _opts ref) -> do Just (GmGhcSession ref) -> do
-- TODO: This is still not enough, there seem to still be references to -- TODO: This is still not enough, there seem to still be references to
-- GHC's state around afterwards. -- GHC's state around afterwards.
liftIO $ writeIORef ref (error "HscEnv: session was dropped") liftIO $ writeIORef ref (error "HscEnv: session was dropped")

View File

@ -188,7 +188,6 @@ instance Monoid GhcModLog where
GhcModLog (ml' `mplus` ml) (vd `mappend` vd') (ls `mappend` ls') GhcModLog (ml' `mplus` ml) (vd `mappend` vd') (ls `mappend` ls')
data GmGhcSession = GmGhcSession { data GmGhcSession = GmGhcSession {
gmgsOptions :: ![GHCOption],
gmgsSession :: !(IORef HscEnv) gmgsSession :: !(IORef HscEnv)
} }

View File

@ -22,20 +22,20 @@ spec = do
runLightGhc env (return ()) `shouldReturn` () runLightGhc env (return ()) `shouldReturn` ()
it "has modules in scope" $ do it "has modules in scope" $ do
withLightHscEnv [] $ \env -> (withLightHscEnv [] $ \env ->
runLightGhc env $ do runLightGhc env $ do
dflags <- getSessionDynFlags dflags <- getSessionDynFlags
let i = intersect (listVisibleModuleNames dflags) let i = intersect (listVisibleModuleNames dflags)
["Control.Applicative", "Control.Arrow" ["Control.Applicative", "Control.Arrow"
,"Control.Exception", "GHC.Exts", "GHC.Float"] ,"Control.Exception", "GHC.Exts", "GHC.Float"]
liftIO $ i `shouldSatisfy` not . null liftIO $ i `shouldSatisfy` not . null) :: IO ()
it "can get module info" $ do it "can get module info" $ do
withLightHscEnv [] $ \env -> (withLightHscEnv [] $ \env ->
runLightGhc env $ do runLightGhc env $ do
mdl <- findModule "Data.List" Nothing mdl <- findModule "Data.List" Nothing
mmi <- getModuleInfo mdl mmi <- getModuleInfo mdl
liftIO $ isJust mmi `shouldBe` True liftIO $ isJust mmi `shouldBe` True) :: IO ()
describe "resolveModule" $ do describe "resolveModule" $ do