Skip to content

Commit

Permalink
Refactor hls-test-util and reduce getCurrentDirectory after initiliza…
Browse files Browse the repository at this point in the history
…tion (#4231)

What's done
* [x] Refactor the `runSession*` family function, properly add `TestConfig`, `runSessionWithTestConfig`, as the most generic `runSession*` function.
* [x] remove raraly used variants of `runSession*` functions and replaced by `runSessionWithTestConfig`. 
* [x] migrate `ExceptionTests ClientSettingsTests CodeLensTests CPPTests CradleTests` to use the `hls-test-utils`
* [x] Only shift to lsp root when current root is different from the lsp root in DefaultMain of ghcide. 
* [x] Remove most usage for `getCurrentDirectory`(After DefaultMain is called), Only remain those in top level of wrapper and exe, implement #3736 (comment)
* [x] add Note [Root Directory]

Co-authored-by: fendor <fendor@users.noreply.github.com>
  • Loading branch information
soulomoon and fendor authored May 27, 2024
1 parent a6cb43b commit 838a51f
Show file tree
Hide file tree
Showing 43 changed files with 589 additions and 468 deletions.
3 changes: 2 additions & 1 deletion exe/Wrapper.hs
Original file line number Diff line number Diff line change
Expand Up @@ -269,7 +269,8 @@ newtype ErrorLSPM c a = ErrorLSPM { unErrorLSPM :: (LspM c) a }
-- to shut down the LSP.
launchErrorLSP :: Recorder (WithPriority (Doc ())) -> T.Text -> IO ()
launchErrorLSP recorder errorMsg = do
let defaultArguments = Main.defaultArguments (cmapWithPrio pretty recorder) (IdePlugins [])
cwd <- getCurrentDirectory
let defaultArguments = Main.defaultArguments (cmapWithPrio pretty recorder) cwd (IdePlugins [])

inH <- Main.argsHandleIn defaultArguments

Expand Down
6 changes: 3 additions & 3 deletions ghcide/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -112,11 +112,11 @@ main = withTelemetryRecorder $ \telemetryRecorder -> do

let arguments =
if argsTesting
then IDEMain.testing (cmapWithPrio LogIDEMain recorder) hlsPlugins
else IDEMain.defaultArguments (cmapWithPrio LogIDEMain recorder) hlsPlugins
then IDEMain.testing (cmapWithPrio LogIDEMain recorder) argsCwd hlsPlugins
else IDEMain.defaultArguments (cmapWithPrio LogIDEMain recorder) argsCwd hlsPlugins

IDEMain.defaultMain (cmapWithPrio LogIDEMain recorder) arguments
{ IDEMain.argsProjectRoot = Just argsCwd
{ IDEMain.argsProjectRoot = argsCwd
, IDEMain.argCommand = argsCommand
, IDEMain.argsHlsPlugins = IDEMain.argsHlsPlugins arguments <> pluginDescToIdePlugins [lspRecorderPlugin]

Expand Down
54 changes: 29 additions & 25 deletions ghcide/session-loader/Development/IDE/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,6 +111,7 @@ import Development.IDE.Types.Shake (WithHieDb, toNoFileKey)
import HieDb.Create
import HieDb.Types
import HieDb.Utils
import Ide.PluginUtils (toAbsolute)
import qualified System.Random as Random
import System.Random (RandomGen)

Expand Down Expand Up @@ -438,7 +439,8 @@ loadSession :: Recorder (WithPriority Log) -> FilePath -> IO (Action IdeGhcSessi
loadSession recorder = loadSessionWithOptions recorder def

loadSessionWithOptions :: Recorder (WithPriority Log) -> SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir = do
let toAbsolutePath = toAbsolute rootDir -- see Note [Root Directory]
cradle_files <- newIORef []
-- Mapping from hie.yaml file to HscEnv, one per hie.yaml file
hscEnvs <- newVar Map.empty :: IO (Var HieMap)
Expand All @@ -459,7 +461,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
-- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path
-- try and normalise that
-- e.g. see https://github.com/haskell/ghcide/issues/126
res' <- traverse makeAbsolute res
let res' = toAbsolutePath <$> res
return $ normalise <$> res'

dummyAs <- async $ return (error "Uninitialised")
Expand Down Expand Up @@ -521,7 +523,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
packageSetup (hieYaml, cfp, opts, libDir) = do
-- Parse DynFlags for the newly discovered component
hscEnv <- emptyHscEnv ideNc libDir
newTargetDfs <- evalGhcEnv hscEnv $ setOptions cfp opts (hsc_dflags hscEnv)
newTargetDfs <- evalGhcEnv hscEnv $ setOptions cfp opts (hsc_dflags hscEnv) rootDir
let deps = componentDependencies opts ++ maybeToList hieYaml
dep_info <- getDependencyInfo deps
-- Now lookup to see whether we are combining with an existing HscEnv
Expand Down Expand Up @@ -588,7 +590,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
-- HscEnv but set the active component accordingly
hscEnv <- emptyHscEnv ideNc _libDir
let new_cache = newComponentCache recorder optExtensions hieYaml _cfp hscEnv
all_target_details <- new_cache old_deps new_deps
all_target_details <- new_cache old_deps new_deps rootDir

this_dep_info <- getDependencyInfo $ maybeToList hieYaml
let (all_targets, this_flags_map, this_options)
Expand Down Expand Up @@ -632,25 +634,20 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do

let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq, [FilePath])
consultCradle hieYaml cfp = do
lfpLog <- flip makeRelative cfp <$> getCurrentDirectory
let lfpLog = makeRelative rootDir cfp
logWith recorder Info $ LogCradlePath lfpLog

when (isNothing hieYaml) $
logWith recorder Warning $ LogCradleNotFound lfpLog

cradle <- loadCradle recorder hieYaml dir
-- TODO: Why are we repeating the same command we have on line 646?
lfp <- flip makeRelative cfp <$> getCurrentDirectory

cradle <- loadCradle recorder hieYaml rootDir
when optTesting $ mRunLspT lspEnv $
sendNotification (SMethod_CustomMethod (Proxy @"ghcide/cradle/loaded")) (toJSON cfp)

-- Display a user friendly progress message here: They probably don't know what a cradle is
let progMsg = "Setting up " <> T.pack (takeBaseName (cradleRootDir cradle))
<> " (for " <> T.pack lfp <> ")"
<> " (for " <> T.pack lfpLog <> ")"
eopts <- mRunLspTCallback lspEnv (\act -> withIndefiniteProgress progMsg Nothing NotCancellable (const act)) $
withTrace "Load cradle" $ \addTag -> do
addTag "file" lfp
addTag "file" lfpLog
old_files <- readIORef cradle_files
res <- cradleToOptsAndLibDir recorder (sessionLoading clientConfig) cradle cfp old_files
addTag "result" (show res)
Expand Down Expand Up @@ -713,7 +710,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
modifyVar_ hscEnvs (const (return Map.empty))

v <- Map.findWithDefault HM.empty hieYaml <$> readVar fileToFlags
cfp <- makeAbsolute file
let cfp = toAbsolutePath file
case HM.lookup (toNormalizedFilePath' cfp) v of
Just (opts, old_di) -> do
deps_ok <- checkDependencyInfo old_di
Expand All @@ -735,7 +732,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
-- before attempting to do so.
let getOptions :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
getOptions file = do
ncfp <- toNormalizedFilePath' <$> makeAbsolute file
let ncfp = toNormalizedFilePath' (toAbsolutePath file)
cachedHieYamlLocation <- HM.lookup ncfp <$> readVar filesMap
hieYaml <- cradleLoc file
sessionOpts (join cachedHieYamlLocation <|> hieYaml, file) `Safe.catch` \e ->
Expand Down Expand Up @@ -814,19 +811,20 @@ fromTargetId :: [FilePath] -- ^ import paths
-> TargetId
-> IdeResult HscEnvEq
-> DependencyInfo
-> FilePath -- ^ root dir, see Note [Root Directory]
-> IO [TargetDetails]
-- For a target module we consider all the import paths
fromTargetId is exts (GHC.TargetModule modName) env dep = do
fromTargetId is exts (GHC.TargetModule modName) env dep dir = do
let fps = [i </> moduleNameSlashes modName -<.> ext <> boot
| ext <- exts
, i <- is
, boot <- ["", "-boot"]
]
locs <- mapM (fmap toNormalizedFilePath' . makeAbsolute) fps
let locs = fmap (toNormalizedFilePath' . toAbsolute dir) fps
return [TargetDetails (TargetModule modName) env dep locs]
-- For a 'TargetFile' we consider all the possible module names
fromTargetId _ _ (GHC.TargetFile f _) env deps = do
nf <- toNormalizedFilePath' <$> makeAbsolute f
fromTargetId _ _ (GHC.TargetFile f _) env deps dir = do
let nf = toNormalizedFilePath' $ toAbsolute dir f
let other
| "-boot" `isSuffixOf` f = toNormalizedFilePath' (L.dropEnd 5 $ fromNormalizedFilePath nf)
| otherwise = toNormalizedFilePath' (fromNormalizedFilePath nf ++ "-boot")
Expand Down Expand Up @@ -915,8 +913,9 @@ newComponentCache
-> HscEnv -- ^ An empty HscEnv
-> [ComponentInfo] -- ^ New components to be loaded
-> [ComponentInfo] -- ^ old, already existing components
-> FilePath -- ^ root dir, see Note [Root Directory]
-> IO [ [TargetDetails] ]
newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis dir = do
let cis = Map.unionWith unionCIs (mkMap new_cis) (mkMap old_cis)
-- When we have multiple components with the same uid,
-- prefer the new one over the old.
Expand Down Expand Up @@ -961,7 +960,7 @@ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do

forM (Map.elems cis) $ \ci -> do
let df = componentDynFlags ci
let createHscEnvEq = maybe newHscEnvEqPreserveImportPaths newHscEnvEq cradlePath
let createHscEnvEq = maybe newHscEnvEqPreserveImportPaths (newHscEnvEq dir) cradlePath
thisEnv <- do
#if MIN_VERSION_ghc(9,3,0)
-- In GHC 9.4 we have multi component support, and we have initialised all the units
Expand All @@ -986,7 +985,7 @@ newComponentCache recorder exts cradlePath _cfp hsc_env old_cis new_cis = do
logWith recorder Debug $ LogNewComponentCache (targetEnv, targetDepends)
evaluate $ liftRnf rwhnf $ componentTargets ci

let mk t = fromTargetId (importPaths df) exts (targetId t) targetEnv targetDepends
let mk t = fromTargetId (importPaths df) exts (targetId t) targetEnv targetDepends dir
ctargets <- concatMapM mk (componentTargets ci)

return (L.nubOrdOn targetTarget ctargets)
Expand Down Expand Up @@ -1171,8 +1170,13 @@ addUnit unit_str = liftEwM $ do
putCmdLineState (unit_str : units)

-- | Throws if package flags are unsatisfiable
setOptions :: GhcMonad m => NormalizedFilePath -> ComponentOptions -> DynFlags -> m (NonEmpty (DynFlags, [GHC.Target]))
setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
setOptions :: GhcMonad m
=> NormalizedFilePath
-> ComponentOptions
-> DynFlags
-> FilePath -- ^ root dir, see Note [Root Directory]
-> m (NonEmpty (DynFlags, [GHC.Target]))
setOptions cfp (ComponentOptions theOpts compRoot _) dflags rootDir = do
((theOpts',_errs,_warns),units) <- processCmdLineP unit_flags [] (map noLoc theOpts)
case NE.nonEmpty units of
Just us -> initMulti us
Expand All @@ -1195,7 +1199,7 @@ setOptions cfp (ComponentOptions theOpts compRoot _) dflags = do
--
-- If we don't end up with a target for the current file in the end, then
-- we will report it as an error for that file
abs_fp <- liftIO $ makeAbsolute (fromNormalizedFilePath cfp)
let abs_fp = toAbsolute rootDir (fromNormalizedFilePath cfp)
let special_target = Compat.mkSimpleTarget df abs_fp
pure $ (df, special_target : targets) :| []
where
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,7 @@ import Development.IDE.Core.Shake as X (FastResult (..),
defineNoDiagnostics,
getClientConfig,
getPluginConfigAction,
ideLogger,
ideLogger, rootDir,
runIdeAction,
shakeExtras, use,
useNoFile,
Expand Down
9 changes: 4 additions & 5 deletions ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,8 +164,7 @@ import Language.LSP.Server (LspT)
import qualified Language.LSP.Server as LSP
import Language.LSP.VFS
import Prelude hiding (mod)
import System.Directory (doesFileExist,
makeAbsolute)
import System.Directory (doesFileExist)
import System.Info.Extra (isWindows)


Expand Down Expand Up @@ -719,13 +718,13 @@ loadGhcSession recorder ghcSessionDepsConfig = do

defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GhcSession file -> do
IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO
-- loading is always returning a absolute path now
(val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file

-- add the deps to the Shake graph
let addDependency fp = do
-- VSCode uses absolute paths in its filewatch notifications
afp <- liftIO $ makeAbsolute fp
let nfp = toNormalizedFilePath' afp
let nfp = toNormalizedFilePath' fp
itExists <- getFileExists nfp
when itExists $ void $ do
use_ GetModificationTime nfp
Expand Down Expand Up @@ -853,7 +852,7 @@ getModIfaceFromDiskAndIndexRule recorder =
hie_loc = Compat.ml_hie_file $ ms_location ms
fileHash <- liftIO $ Util.getFileHash hie_loc
mrow <- liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb (fromNormalizedFilePath f))
hie_loc' <- liftIO $ traverse (makeAbsolute . HieDb.hieModuleHieFile) mrow
let hie_loc' = HieDb.hieModuleHieFile <$> mrow
case mrow of
Just row
| fileHash == HieDb.modInfoHash (HieDb.hieModInfo row)
Expand Down
8 changes: 5 additions & 3 deletions ghcide/src/Development/IDE/Core/Service.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,8 +67,9 @@ initialise :: Recorder (WithPriority Log)
-> WithHieDb
-> IndexQueue
-> Monitoring
-> FilePath -- ^ Root directory see Note [Root Directory]
-> IO IdeState
initialise recorder defaultConfig plugins mainRule lspEnv debouncer options withHieDb hiedbChan metrics = do
initialise recorder defaultConfig plugins mainRule lspEnv debouncer options withHieDb hiedbChan metrics rootDir = do
shakeProfiling <- do
let fromConf = optShakeProfiling options
fromEnv <- lookupEnv "GHCIDE_BUILD_PROFILING"
Expand All @@ -86,11 +87,12 @@ initialise recorder defaultConfig plugins mainRule lspEnv debouncer options with
hiedbChan
(optShakeOptions options)
metrics
$ do
(do
addIdeGlobal $ GlobalIdeOptions options
ofInterestRules (cmapWithPrio LogOfInterest recorder)
fileExistsRules (cmapWithPrio LogFileExists recorder) lspEnv
mainRule
mainRule)
rootDir

-- | Shutdown the Compiler Service.
shutdown :: IdeState -> IO ()
Expand Down
36 changes: 34 additions & 2 deletions ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@
-- always stored as real Haskell values, whereas Shake serialises all 'A' values
-- between runs. To deserialise a Shake value, we just consult Values.
module Development.IDE.Core.Shake(
IdeState, shakeSessionInit, shakeExtras, shakeDb,
IdeState, shakeSessionInit, shakeExtras, shakeDb, rootDir,
ShakeExtras(..), getShakeExtras, getShakeExtrasRules,
KnownTargets, Target(..), toKnownFiles,
IdeRule, IdeResult,
Expand Down Expand Up @@ -527,6 +527,33 @@ newtype ShakeSession = ShakeSession
-- ^ Closes the Shake session
}

-- Note [Root Directory]
-- ~~~~~~~~~~~~~~~~~~~~~
-- We keep track of the root directory explicitly, which is the directory of the project root.
-- We might be setting it via these options with decreasing priority:
--
-- 1. from LSP workspace root, `resRootPath` in `LanguageContextEnv`.
-- 2. command line (--cwd)
-- 3. default to the current directory.
--
-- Using `getCurrentDirectory` makes it more difficult to run the tests, as we spawn one thread of HLS per test case.
-- If we modify the global Variable CWD, via `setCurrentDirectory`, all other test threads are suddenly affected,
-- forcing us to run all integration tests sequentially.
--
-- Also, there might be a race condition if we depend on the current directory, as some plugin might change it.
-- e.g. stylish's `loadConfig`. https://github.com/haskell/haskell-language-server/issues/4234
--
-- But according to https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#workspace_workspaceFolders
-- The root dir is deprecated, that means we should cleanup dependency on the project root(Or $CWD) thing gradually,
-- so multi-workspaces can actually be supported when we use absolute path everywhere(might also need some high level design).
-- That might not be possible unless we have everything adapted to it, like 'hlint' and 'evaluation of template haskell'.
-- But we should still be working towards the goal.
--
-- We can drop it in the future once:
-- 1. We can get rid all the usages of root directory in the codebase.
-- 2. LSP version we support actually removes the root directory from the protocol.
--

-- | A Shake database plus persistent store. Can be thought of as storing
-- mappings from @(FilePath, k)@ to @RuleResult k@.
data IdeState = IdeState
Expand All @@ -535,6 +562,8 @@ data IdeState = IdeState
,shakeExtras :: ShakeExtras
,shakeDatabaseProfile :: ShakeDatabase -> IO (Maybe FilePath)
,stopMonitoring :: IO ()
-- | See Note [Root Directory]
,rootDir :: FilePath
}


Expand Down Expand Up @@ -623,11 +652,14 @@ shakeOpen :: Recorder (WithPriority Log)
-> ShakeOptions
-> Monitoring
-> Rules ()
-> FilePath
-- ^ Root directory, this one might be picking up from `LanguageContextEnv`'s `resRootPath`
-- , see Note [Root Directory]
-> IO IdeState
shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
shakeProfileDir (IdeReportProgress reportProgress)
ideTesting@(IdeTesting testing)
withHieDb indexQueue opts monitoring rules = mdo
withHieDb indexQueue opts monitoring rules rootDir = mdo

#if MIN_VERSION_ghc(9,3,0)
ideNc <- initNameCache 'r' knownKeyNames
Expand Down
Loading

0 comments on commit 838a51f

Please sign in to comment.