Skip to content

Commit f971c4c

Browse files
committed
Add POC for HLS loading multiple components on startup
Powered by hie-bios.
1 parent b8bb06e commit f971c4c

File tree

3 files changed

+92
-66
lines changed

3 files changed

+92
-66
lines changed

cabal.project

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,11 @@ source-repository-package
3434
location: https://github.com/hsyl20/ghc-api-compat
3535
tag: 8fee87eac97a538dbe81ff1ab18cff10f2f9fa15
3636

37+
source-repository-package
38+
type: git
39+
location: https://github.com/fendor/hie-bios
40+
tag: fe823adfa0e82aa76e098a57cc424c92902e1db8
41+
3742
write-ghc-environment-files: never
3843

3944
index-state: 2021-06-30T16:00:00Z

ghcide/ghcide.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,7 @@ library
100100
ghc-paths,
101101
ghc-api-compat,
102102
cryptohash-sha1 >=0.11.100 && <0.12,
103-
hie-bios >= 0.7.1 && < 0.8.0,
103+
hie-bios >= 0.7.1 && < 0.9.0,
104104
implicit-hie-cradle >= 0.3.0.2 && < 0.4,
105105
base16-bytestring >=0.1.1 && <1.1
106106
if os(windows)

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 86 additions & 65 deletions
Original file line numberDiff line numberDiff line change
@@ -86,6 +86,8 @@ import HieDb.Create
8686
import HieDb.Types
8787
import HieDb.Utils
8888
import Ide.Types (dynFlagsModifyGlobal)
89+
import Data.List.NonEmpty (NonEmpty)
90+
import qualified Data.List.NonEmpty as NE
8991

9092
-- | Bump this version number when making changes to the format of the data stored in hiedb
9193
hiedbDataVersion :: String
@@ -231,7 +233,9 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
231233
filesMap <- newVar HM.empty :: IO (Var FilesMap)
232234
-- Version of the mappings above
233235
version <- newVar 0
234-
let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
236+
let returnWithVersion :: (FilePath -> IO (IdeResult HscEnvEq, [FilePath]))
237+
-> Action IdeGhcSession
238+
returnWithVersion fun = (IdeGhcSession fun) <$> liftIO (readVar version)
235239
-- This caches the mapping from Mod.hs -> hie.yaml
236240
cradleLoc <- liftIO $ memoIO $ \v -> do
237241
res <- findCradle v
@@ -278,9 +282,9 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
278282
-- If the hieYaml file already has an HscEnv, the new component is
279283
-- combined with the components in the old HscEnv into a new HscEnv
280284
-- which contains the union.
281-
let packageSetup :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
282-
-> IO (HscEnv, ComponentInfo, [ComponentInfo])
283-
packageSetup (hieYaml, cfp, opts, libDir) = do
285+
let packageSetup :: (Maybe FilePath, NormalizedFilePath, NonEmpty ComponentOptions, FilePath)
286+
-> IO [(HscEnv, ComponentInfo, [ComponentInfo])]
287+
packageSetup (hieYaml, cfp, allOpts, libDir) = concatForM (NE.toList allOpts) $ \opts -> do
284288
-- Parse DynFlags for the newly discovered component
285289
hscEnv <- emptyHscEnv ideNc libDir
286290
(df, targets) <- evalGhcEnv hscEnv $
@@ -291,7 +295,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
291295
-- or making a new one. The lookup returns the HscEnv and a list of
292296
-- information about other components loaded into the HscEnv
293297
-- (unitId, DynFlag, Targets)
294-
modifyVar hscEnvs $ \m -> do
298+
r <- modifyVar hscEnvs $ \m -> do
295299
-- Just deps if there's already an HscEnv
296300
-- Nothing is it's the first time we are making an HscEnv
297301
let oldDeps = Map.lookup hieYaml m
@@ -345,12 +349,13 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
345349
-- . The modified information (without -inplace flags) for
346350
-- existing packages
347351
pure (Map.insert hieYaml (newHscEnv, new_deps) m, (newHscEnv, head new_deps', tail new_deps'))
352+
pure [r]
348353

349354

350-
let session :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
355+
let session :: (Maybe FilePath, NormalizedFilePath, NonEmpty ComponentOptions, FilePath)
351356
-> IO (IdeResult HscEnvEq,[FilePath])
352-
session args@(hieYaml, _cfp, _opts, _libDir) = do
353-
(hscEnv, new, old_deps) <- packageSetup args
357+
session args@(hieYaml, cfp, _opts, _libDir) = do
358+
setupInfos <- packageSetup args -- (hscEnvs, new, old_deps)
354359

355360
-- Whenever we spin up a session on Linux, dynamically load libm.so.6
356361
-- in. We need this in case the binary is statically linked, in which
@@ -360,58 +365,73 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
360365
-- some code. If the binary is dynamically linked, then this will have
361366
-- no effect.
362367
-- See https://github.com/haskell/haskell-language-server/issues/221
363-
when (os == "linux") $ do
364-
initObjLinker hscEnv
365-
res <- loadDLL hscEnv "libm.so.6"
366-
case res of
367-
Nothing -> pure ()
368-
Just err -> hPutStrLn stderr $
369-
"Error dynamically loading libm.so.6:\n" <> err
370-
371-
-- Make a map from unit-id to DynFlags, this is used when trying to
372-
-- resolve imports. (especially PackageImports)
373-
let uids = map (\ci -> (componentUnitId ci, componentDynFlags ci)) (new : old_deps)
374-
375-
-- For each component, now make a new HscEnvEq which contains the
376-
-- HscEnv for the hie.yaml file but the DynFlags for that component
377-
378-
-- New HscEnv for the component in question, returns the new HscEnvEq and
379-
-- a mapping from FilePath to the newly created HscEnvEq.
380-
let new_cache = newComponentCache logger optExtensions hieYaml _cfp hscEnv uids
381-
(cs, res) <- new_cache new
382-
-- Modified cache targets for everything else in the hie.yaml file
383-
-- which now uses the same EPS and so on
384-
cached_targets <- concatMapM (fmap fst . new_cache) old_deps
385-
386-
let all_targets = cs ++ cached_targets
387-
388-
void $ modifyVar' fileToFlags $
389-
Map.insert hieYaml (HM.fromList (concatMap toFlagsMap all_targets))
390-
void $ modifyVar' filesMap $
391-
flip HM.union (HM.fromList (zip (map fst $ concatMap toFlagsMap all_targets) (repeat hieYaml)))
392-
393-
void $ extendKnownTargets all_targets
394-
395-
-- Invalidate all the existing GhcSession build nodes by restarting the Shake session
396-
invalidateShakeCache
397-
restartShakeSession []
398-
399-
-- Typecheck all files in the project on startup
400-
checkProject <- getCheckProject
401-
unless (null cs || not checkProject) $ do
402-
cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) (concatMap targetLocations cs)
403-
void $ shakeEnqueue extras $ mkDelayedAction "InitialLoad" Debug $ void $ do
404-
mmt <- uses GetModificationTime cfps'
405-
let cs_exist = catMaybes (zipWith (<$) cfps' mmt)
406-
modIfaces <- uses GetModIface cs_exist
407-
-- update exports map
408-
extras <- getShakeExtras
409-
let !exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
410-
liftIO $ modifyVar_ (exportsMap extras) $ evaluate . (exportsMap' <>)
411-
412-
return (second Map.keys res)
413-
414-
let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq, [FilePath])
368+
forM_ setupInfos $ \(hscEnv, new, old_deps) -> do
369+
when (os == "linux") $ do
370+
initObjLinker hscEnv
371+
res <- loadDLL hscEnv "libm.so.6"
372+
case res of
373+
Nothing -> pure ()
374+
Just err -> hPutStrLn stderr $
375+
"Error dynamically loading libm.so.6:\n" <> err
376+
377+
-- Make a map from unit-id to DynFlags, this is used when trying to
378+
-- resolve imports. (especially PackageImports)
379+
let uids = map (\ci -> (componentUnitId ci, componentDynFlags ci)) (new : old_deps)
380+
381+
-- For each component, now make a new HscEnvEq which contains the
382+
-- HscEnv for the hie.yaml file but the DynFlags for that component
383+
384+
-- New HscEnv for the component in question, returns the new HscEnvEq and
385+
-- a mapping from FilePath to the newly created HscEnvEq.
386+
let new_cache = newComponentCache logger optExtensions hieYaml cfp hscEnv uids
387+
(cs, _res) <- new_cache new
388+
-- Modified cache targets for everything else in the hie.yaml file
389+
-- which now uses the same EPS and so on
390+
cached_targets <- concatMapM (fmap fst . new_cache) old_deps
391+
392+
let all_targets = cs ++ cached_targets
393+
394+
void $ modifyVar' fileToFlags $
395+
Map.insert hieYaml (HM.fromList (concatMap toFlagsMap all_targets))
396+
void $ modifyVar' filesMap $
397+
flip HM.union (HM.fromList (zip (map fst $ concatMap toFlagsMap all_targets) (repeat hieYaml)))
398+
399+
void $ extendKnownTargets all_targets
400+
401+
-- Invalidate all the existing GhcSession build nodes by restarting the Shake session
402+
invalidateShakeCache
403+
restartShakeSession []
404+
405+
-- Typecheck all files in the project on startup
406+
checkProject <- getCheckProject
407+
unless (null cs || not checkProject) $ do
408+
cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) (concatMap targetLocations cs)
409+
void $ shakeEnqueue extras $ mkDelayedAction "InitialLoad" Debug $ void $ do
410+
mmt <- uses GetModificationTime cfps'
411+
let cs_exist = catMaybes (zipWith (<$) cfps' mmt)
412+
modIfaces <- uses GetModIface cs_exist
413+
-- update exports map
414+
extras <- getShakeExtras
415+
let !exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
416+
liftIO $ modifyVar_ (exportsMap extras) $ evaluate . (exportsMap' <>)
417+
418+
yamlMap <- readVar fileToFlags
419+
let (hscEnvEq, depInfo) = (yamlMap Map.! hieYaml) HM.! cfp
420+
pure (hscEnvEq, Map.keys depInfo)
421+
422+
-- Let's be insanely hacky!
423+
-- Go through all new components and find the one that the given fp most likely
424+
-- belongs to.
425+
-- Since all ComponentInfo's carry a proof for which file caused their creation,
426+
-- and add this file to their targets, we need to do some post-processing.
427+
-- It is an implementation detail that the first known target is the normalized
428+
-- filepath of the proof file.
429+
-- Let's strip it away and let's see whether the targets still contain 'cfp'!
430+
-- If they do, it must be the home component of cfp.
431+
-- If we find it, remove it as a target from all other 'HscEnvEq' to avoid recompilation
432+
-- issues.
433+
434+
let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq,[FilePath])
415435
consultCradle hieYaml cfp = do
416436
lfp <- flip makeRelative cfp <$> getCurrentDirectory
417437
logInfo logger $ T.pack ("Consulting the cradle for " <> show lfp)
@@ -443,7 +463,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
443463
InstallationMismatch{..} ->
444464
return (([renderPackageSetupException cfp GhcVersionMismatch{..}], Nothing),[])
445465
InstallationChecked _compileTime _ghcLibCheck ->
446-
session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
466+
session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
447467
-- Failure case, either a cradle error or the none cradle
448468
Left err -> do
449469
dep_info <- getDependencyInfo (maybeToList hieYaml)
@@ -500,7 +520,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
500520
-- GHC options/dynflags needed for the session and the GHC library directory
501521

502522
cradleToOptsAndLibDir :: Show a => Cradle a -> FilePath
503-
-> IO (Either [CradleError] (ComponentOptions, FilePath))
523+
-> IO (Either [CradleError] (NonEmpty ComponentOptions, FilePath))
504524
cradleToOptsAndLibDir cradle file = do
505525
-- Start off by getting the session options
506526
let showLine s = hPutStrLn stderr ("> " ++ s)
@@ -577,7 +597,7 @@ newComponentCache
577597
-> [(InstalledUnitId, DynFlags)]
578598
-> ComponentInfo
579599
-> IO ( [TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
580-
newComponentCache logger exts cradlePath cfp hsc_env uids ci = do
600+
newComponentCache logger exts cradlePath _cfp hsc_env uids ci = do
581601
let df = componentDynFlags ci
582602
let hscEnv' = hsc_env { hsc_dflags = df
583603
, hsc_IC = (hsc_IC hsc_env) { ic_dflags = df } }
@@ -597,8 +617,9 @@ newComponentCache logger exts cradlePath cfp hsc_env uids ci = do
597617
-- the component, in which case things will be horribly broken anyway.
598618
-- Otherwise, we will immediately attempt to reload this module which
599619
-- causes an infinite loop and high CPU usage.
600-
let special_target = TargetDetails (TargetFile cfp) targetEnv targetDepends [componentFP ci]
601-
return (special_target:ctargets, res)
620+
-- let special_target = TargetDetails (TargetFile cfp) targetEnv targetDepends [componentFP ci]
621+
-- return (special_target:ctargets, res)
622+
return (ctargets, res)
602623

603624
{- Note [Avoiding bad interface files]
604625
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

0 commit comments

Comments
 (0)