@@ -424,7 +424,7 @@ getHieDbLoc dir = do
424424loadSessionWithOptions :: Recorder (WithPriority Log ) -> SessionLoadingOptions -> FilePath -> TQueue (IO () ) -> IO (Action IdeGhcSession )
425425loadSessionWithOptions recorder SessionLoadingOptions {.. } rootDir que = do
426426 let toAbsolutePath = toAbsolute rootDir -- see Note [Root Directory]
427- cradle_files <- newIORef []
427+ cradle_files <- newIORef ( Set. fromList [] )
428428 -- Mapping from hie.yaml file to HscEnv, one per hie.yaml file
429429 hscEnvs <- newVar Map. empty :: IO (Var HieMap )
430430 -- Mapping from a Filepath to HscEnv
@@ -434,6 +434,8 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
434434 -- they are inconsistent. So, everywhere you modify 'fileToFlags',
435435 -- you have to modify 'filesMap' as well.
436436 filesMap <- newVar HM. empty :: IO (Var FilesMap )
437+ pendingFilesTQueue <- newTQueueIO
438+ -- Pending files waiting to be loaded
437439 -- Version of the mappings above
438440 version <- newVar 0
439441 biosSessionLoadingVar <- newVar Nothing :: IO (Var (Maybe SessionLoadingPreferenceConfig ))
@@ -550,7 +552,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
550552
551553
552554 let session :: (Maybe FilePath , NormalizedFilePath , ComponentOptions , FilePath )
553- -> IO (IdeResult HscEnvEq ,[FilePath ])
555+ -> IO (( IdeResult HscEnvEq ,[FilePath ]), HashSet FilePath )
554556 session args@ (hieYaml, _cfp, _opts, _libDir) = do
555557 (new_deps, old_deps) <- packageSetup args
556558
@@ -562,13 +564,15 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
562564 let new_cache = newComponentCache recorder optExtensions _cfp hscEnv
563565 all_target_details <- new_cache old_deps new_deps
564566
567+ let flags_map' = HM. fromList (concatMap toFlagsMap all_targets')
568+ all_targets' = concat all_target_details
569+ newLoaded = HM. keys flags_map'
565570 this_dep_info <- getDependencyInfo $ maybeToList hieYaml
566571 let (all_targets, this_flags_map, this_options)
567572 = case HM. lookup _cfp flags_map' of
568573 Just this -> (all_targets', flags_map', this)
569574 Nothing -> (this_target_details : all_targets', HM. insert _cfp this_flags flags_map', this_flags)
570- where all_targets' = concat all_target_details
571- flags_map' = HM. fromList (concatMap toFlagsMap all_targets')
575+ where
572576 this_target_details = TargetDetails (TargetFile _cfp) this_error_env this_dep_info [_cfp]
573577 this_flags = (this_error_env, this_dep_info)
574578 this_error_env = ([this_error], Nothing )
@@ -580,27 +584,27 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
580584
581585 void $ modifyVar' fileToFlags $ Map. insert hieYaml this_flags_map
582586 void $ modifyVar' filesMap $ flip HM. union (HM. fromList (map ((,hieYaml) . fst ) $ concatMap toFlagsMap all_targets))
587+ -- Typecheck all files in the project on startup
588+ checkProject <- getCheckProject
583589 -- The VFS doesn't change on cradle edits, re-use the old one.
584590 -- Invalidate all the existing GhcSession build nodes by restarting the Shake session
585- keys2 <- invalidateShakeCache
586591 restartShakeSession VFSUnmodified " new component" [] $ do
592+ keys2 <- invalidateShakeCache
587593 keys1 <- extendKnownTargets all_targets
594+ unless (null new_deps || not checkProject) $ do
595+ cfps' <- liftIO $ filterM (IO. doesFileExist . fromNormalizedFilePath) (concatMap targetLocations all_targets)
596+ void $ shakeEnqueue extras $ mkDelayedAction " InitialLoad" Debug $ void $ do
597+ mmt <- uses GetModificationTime cfps'
598+ let cs_exist = catMaybes (zipWith (<$) cfps' mmt)
599+ modIfaces <- uses GetModIface cs_exist
600+ -- update exports map
601+ shakeExtras <- getShakeExtras
602+ let ! exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
603+ liftIO $ atomically $ modifyTVar' (exportsMap shakeExtras) (exportsMap' <> )
588604 return [keys1, keys2]
589605
590- -- Typecheck all files in the project on startup
591- checkProject <- getCheckProject
592- unless (null new_deps || not checkProject) $ do
593- cfps' <- liftIO $ filterM (IO. doesFileExist . fromNormalizedFilePath) (concatMap targetLocations all_targets)
594- void $ shakeEnqueue extras $ mkDelayedAction " InitialLoad" Debug $ void $ do
595- mmt <- uses GetModificationTime cfps'
596- let cs_exist = catMaybes (zipWith (<$) cfps' mmt)
597- modIfaces <- uses GetModIface cs_exist
598- -- update exports map
599- shakeExtras <- getShakeExtras
600- let ! exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
601- liftIO $ atomically $ modifyTVar' (exportsMap shakeExtras) (exportsMap' <> )
602-
603- return $ second Map. keys this_options
606+
607+ return $ (second Map. keys this_options, Set. fromList $ fromNormalizedFilePath <$> newLoaded)
604608
605609 let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq , [FilePath ])
606610 consultCradle hieYaml cfp = do
@@ -615,11 +619,13 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
615619 -- Display a user friendly progress message here: They probably don't know what a cradle is
616620 let progMsg = " Setting up " <> T. pack (takeBaseName (cradleRootDir cradle))
617621 <> " (for " <> T. pack lfpLog <> " )"
622+
623+ pendingFiles <- Set. fromList <$> (atomically $ flushTQueue pendingFilesTQueue)
618624 eopts <- mRunLspTCallback lspEnv (\ act -> withIndefiniteProgress progMsg Nothing NotCancellable (const act)) $
619625 withTrace " Load cradle" $ \ addTag -> do
620626 addTag " file" lfpLog
621627 old_files <- readIORef cradle_files
622- res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
628+ res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp ( Set. toList $ pendingFiles <> old_files)
623629 addTag " result" (show res)
624630 return res
625631
@@ -633,8 +639,12 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
633639 [] -> error $ " GHC version could not be parsed: " <> version
634640 ((runTime, _): _)
635641 | compileTime == runTime -> do
636- atomicModifyIORef' cradle_files (\ xs -> (cfp: xs,() ))
637- session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
642+ (results, newLoaded) <- session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
643+ -- put back to pending que if not listed in the results
644+ let remainPendingFiles = Set. delete cfp $ pendingFiles `Set.difference` newLoaded
645+ atomically $ forM_ remainPendingFiles (writeTQueue pendingFilesTQueue)
646+ atomicModifyIORef' cradle_files (\ xs -> (pendingFiles `Set.intersection` newLoaded <> xs,() ))
647+ return results
638648 | otherwise -> return (([renderPackageSetupException cfp GhcVersionMismatch {.. }], Nothing ),[] )
639649 -- Failure case, either a cradle error or the none cradle
640650 Left err -> do
@@ -708,6 +718,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
708718 return (([renderPackageSetupException file e], Nothing ), maybe [] pure hieYaml)
709719
710720 returnWithVersion $ \ file -> do
721+ atomically $ writeTQueue pendingFilesTQueue $ toAbsolutePath file
711722 -- see Note [Serializing runs in separate thread]
712723 awaitRunInThread que $ getOptions file
713724
0 commit comments