@@ -86,6 +86,8 @@ import HieDb.Create
86
86
import HieDb.Types
87
87
import HieDb.Utils
88
88
import Ide.Types (dynFlagsModifyGlobal )
89
+ import Data.List.NonEmpty (NonEmpty )
90
+ import qualified Data.List.NonEmpty as NE
89
91
90
92
-- | Bump this version number when making changes to the format of the data stored in hiedb
91
93
hiedbDataVersion :: String
@@ -231,7 +233,9 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
231
233
filesMap <- newVar HM. empty :: IO (Var FilesMap )
232
234
-- Version of the mappings above
233
235
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)
235
239
-- This caches the mapping from Mod.hs -> hie.yaml
236
240
cradleLoc <- liftIO $ memoIO $ \ v -> do
237
241
res <- findCradle v
@@ -278,9 +282,9 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
278
282
-- If the hieYaml file already has an HscEnv, the new component is
279
283
-- combined with the components in the old HscEnv into a new HscEnv
280
284
-- 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
284
288
-- Parse DynFlags for the newly discovered component
285
289
hscEnv <- emptyHscEnv ideNc libDir
286
290
(df, targets) <- evalGhcEnv hscEnv $
@@ -291,7 +295,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
291
295
-- or making a new one. The lookup returns the HscEnv and a list of
292
296
-- information about other components loaded into the HscEnv
293
297
-- (unitId, DynFlag, Targets)
294
- modifyVar hscEnvs $ \ m -> do
298
+ r <- modifyVar hscEnvs $ \ m -> do
295
299
-- Just deps if there's already an HscEnv
296
300
-- Nothing is it's the first time we are making an HscEnv
297
301
let oldDeps = Map. lookup hieYaml m
@@ -345,12 +349,13 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
345
349
-- . The modified information (without -inplace flags) for
346
350
-- existing packages
347
351
pure (Map. insert hieYaml (newHscEnv, new_deps) m, (newHscEnv, head new_deps', tail new_deps'))
352
+ pure [r]
348
353
349
354
350
- let session :: (Maybe FilePath , NormalizedFilePath , ComponentOptions , FilePath )
355
+ let session :: (Maybe FilePath , NormalizedFilePath , NonEmpty ComponentOptions , FilePath )
351
356
-> 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)
354
359
355
360
-- Whenever we spin up a session on Linux, dynamically load libm.so.6
356
361
-- in. We need this in case the binary is statically linked, in which
@@ -360,58 +365,73 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
360
365
-- some code. If the binary is dynamically linked, then this will have
361
366
-- no effect.
362
367
-- 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 ])
415
435
consultCradle hieYaml cfp = do
416
436
lfp <- flip makeRelative cfp <$> getCurrentDirectory
417
437
logInfo logger $ T. pack (" Consulting the cradle for " <> show lfp)
@@ -443,7 +463,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
443
463
InstallationMismatch {.. } ->
444
464
return (([renderPackageSetupException cfp GhcVersionMismatch {.. }], Nothing ),[] )
445
465
InstallationChecked _compileTime _ghcLibCheck ->
446
- session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
466
+ session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
447
467
-- Failure case, either a cradle error or the none cradle
448
468
Left err -> do
449
469
dep_info <- getDependencyInfo (maybeToList hieYaml)
@@ -500,7 +520,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
500
520
-- GHC options/dynflags needed for the session and the GHC library directory
501
521
502
522
cradleToOptsAndLibDir :: Show a => Cradle a -> FilePath
503
- -> IO (Either [CradleError ] (ComponentOptions , FilePath ))
523
+ -> IO (Either [CradleError ] (NonEmpty ComponentOptions , FilePath ))
504
524
cradleToOptsAndLibDir cradle file = do
505
525
-- Start off by getting the session options
506
526
let showLine s = hPutStrLn stderr (" > " ++ s)
@@ -577,7 +597,7 @@ newComponentCache
577
597
-> [(InstalledUnitId , DynFlags )]
578
598
-> ComponentInfo
579
599
-> 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
581
601
let df = componentDynFlags ci
582
602
let hscEnv' = hsc_env { hsc_dflags = df
583
603
, hsc_IC = (hsc_IC hsc_env) { ic_dflags = df } }
@@ -597,8 +617,9 @@ newComponentCache logger exts cradlePath cfp hsc_env uids ci = do
597
617
-- the component, in which case things will be horribly broken anyway.
598
618
-- Otherwise, we will immediately attempt to reload this module which
599
619
-- 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)
602
623
603
624
{- Note [Avoiding bad interface files]
604
625
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
0 commit comments