diff --git a/ghcide/ghcide.cabal b/ghcide/ghcide.cabal index bf88a55ed3..9c93aecc08 100644 --- a/ghcide/ghcide.cabal +++ b/ghcide/ghcide.cabal @@ -135,6 +135,7 @@ library Development.IDE.Core.FileStore Development.IDE.Core.FileUtils Development.IDE.Core.IdeConfiguration + Development.IDE.Core.InputPath Development.IDE.Core.OfInterest Development.IDE.Core.PluginUtils Development.IDE.Core.PositionMapping diff --git a/ghcide/session-loader/Development/IDE/Session.hs b/ghcide/session-loader/Development/IDE/Session.hs index a1d778ab0e..23fd84c714 100644 --- a/ghcide/session-loader/Development/IDE/Session.hs +++ b/ghcide/session-loader/Development/IDE/Session.hs @@ -125,6 +125,7 @@ import GHC.Driver.Errors.Types import GHC.Types.Error (errMsgDiagnostic, singleMessage) import GHC.Unit.State +import Development.IDE.Core.InputPath (generalizeProjectInput, classifyProjectHaskellInputs) data Log = LogSettingInitialDynFlags @@ -592,8 +593,9 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do unless (null new_deps || not checkProject) $ do cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) (concatMap targetLocations all_targets) void $ shakeEnqueue extras $ mkDelayedAction "InitialLoad" Debug $ void $ do - mmt <- uses GetModificationTime cfps' - let cs_exist = catMaybes (zipWith (<$) cfps' mmt) + let cfps'' = classifyProjectHaskellInputs cfps' + mmt <- uses GetModificationTime $ generalizeProjectInput <$> cfps'' + let cs_exist = catMaybes (zipWith (<$) cfps'' mmt) modIfaces <- uses GetModIface cs_exist -- update exports map shakeExtras <- getShakeExtras diff --git a/ghcide/src/Development/IDE/Core/Actions.hs b/ghcide/src/Development/IDE/Core/Actions.hs index 20c86c8280..d7bbef309b 100644 --- a/ghcide/src/Development/IDE/Core/Actions.hs +++ b/ghcide/src/Development/IDE/Core/Actions.hs @@ -32,6 +32,7 @@ import Language.LSP.Protocol.Types (DocumentHighlight (..), SymbolInformation (..), normalizedFilePathToUri, uriToNormalizedFilePath) +import Development.IDE.Core.InputPath (classifyProjectHaskellInputs, InputPath (InputPath)) -- | Eventually this will lookup/generate URIs for files in dependencies, but not in the @@ -59,12 +60,22 @@ getAtPoint file pos = runMaybeT $ do ide <- ask opts <- liftIO $ getIdeOptionsIO ide - (hf, mapping) <- useWithStaleFastMT GetHieAst file - env <- hscEnv . fst <$> useWithStaleFastMT GhcSession file - dkMap <- lift $ maybe (DKMap mempty mempty) fst <$> runMaybeT (useWithStaleFastMT GetDocMap file) + (hf, mapping) <- useWithStaleFastMT GetHieAst $ InputPath file + -- The HscEnv and DKMap are not strictly necessary for hover + -- to work, so we only calculate them for project files, not + -- for dependency files. They provide information that will + -- not be displayed in dependency files. See the atPoint + -- function in ghcide/src/Development/IDE/Spans/AtPoint.hs + -- for the specifics of how they are used. + (mEnv, mDkMap) <- case classifyProjectHaskellInputs [file] of + [] -> pure (Nothing, Nothing) + projectInput:_ -> do + env <- hscEnv . fst <$> useWithStaleFastMT GhcSession projectInput + dkMap <- lift $ maybe (DKMap mempty mempty) fst <$> runMaybeT (useWithStaleFastMT GetDocMap projectInput) + pure (Just env, Just dkMap) !pos' <- MaybeT (return $ fromCurrentPosition mapping pos) - MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<<)) <$> AtPoint.atPoint opts hf dkMap env pos' + MaybeT $ liftIO $ fmap (first (toCurrentRange mapping =<<)) <$> AtPoint.atPoint opts hf mDkMap mEnv pos' -- | Converts locations in the source code to their current positions, -- taking into account changes that may have occurred due to edits. @@ -87,7 +98,7 @@ toCurrentLocation mapping file (Location uri range) = else do otherLocationMapping <- fmap (fmap snd) $ runMaybeT $ do otherLocationFile <- MaybeT $ pure $ uriToNormalizedFilePath nUri - useWithStaleFastMT GetHieAst otherLocationFile + useWithStaleFastMT GetHieAst $ InputPath otherLocationFile pure $ Location uri <$> (flip toCurrentRange range =<< otherLocationMapping) where nUri :: NormalizedUri @@ -98,8 +109,10 @@ getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Location, getDefinition file pos = runMaybeT $ do ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask opts <- liftIO $ getIdeOptionsIO ide - (HAR _ hf _ _ _, mapping) <- useWithStaleFastMT GetHieAst file - (ImportMap imports, _) <- useWithStaleFastMT GetImportMap file + (HAR _ hf _ _ _, mapping) <- useWithStaleFastMT GetHieAst $ InputPath file + (ImportMap imports, _) <- case classifyProjectHaskellInputs [file] of + [] -> pure (ImportMap mempty, PositionMapping idDelta) + (projectInput: _) -> useWithStaleFastMT GetImportMap projectInput !pos' <- MaybeT (pure $ fromCurrentPosition mapping pos) locationsWithIdentifier <- AtPoint.gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos' mapMaybeM (\(location, identifier) -> do @@ -112,7 +125,7 @@ getTypeDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [(Locati getTypeDefinition file pos = runMaybeT $ do ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask opts <- liftIO $ getIdeOptionsIO ide - (hf, mapping) <- useWithStaleFastMT GetHieAst file + (hf, mapping) <- useWithStaleFastMT GetHieAst $ InputPath file !pos' <- MaybeT (return $ fromCurrentPosition mapping pos) locationsWithIdentifier <- AtPoint.gotoTypeDefinition withHieDb (lookupMod hiedbWriter) opts hf pos' mapMaybeM (\(location, identifier) -> do @@ -122,7 +135,7 @@ getTypeDefinition file pos = runMaybeT $ do highlightAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe [DocumentHighlight]) highlightAtPoint file pos = runMaybeT $ do - (HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst file + (HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst $ InputPath file !pos' <- MaybeT (return $ fromCurrentPosition mapping pos) let toCurrentHighlight (DocumentHighlight range t) = flip DocumentHighlight t <$> toCurrentRange mapping range mapMaybe toCurrentHighlight <$>AtPoint.documentHighlight hf rf pos' @@ -132,7 +145,7 @@ refsAtPoint :: NormalizedFilePath -> Position -> Action [Location] refsAtPoint file pos = do ShakeExtras{withHieDb} <- getShakeExtras fs <- HM.keys <$> getFilesOfInterestUntracked - asts <- HM.fromList . mapMaybe sequence . zip fs <$> usesWithStale GetHieAst fs + asts <- HM.fromList . mapMaybe sequence . zip fs <$> usesWithStale GetHieAst (map InputPath fs) AtPoint.referencesAtPoint withHieDb file pos (AtPoint.FOIReferences asts) workspaceSymbols :: T.Text -> IdeAction (Maybe [SymbolInformation]) diff --git a/ghcide/src/Development/IDE/Core/FileExists.hs b/ghcide/src/Development/IDE/Core/FileExists.hs index 280cd14028..b2784eb920 100644 --- a/ghcide/src/Development/IDE/Core/FileExists.hs +++ b/ghcide/src/Development/IDE/Core/FileExists.hs @@ -39,6 +39,8 @@ import Language.LSP.Server hiding (getVirtualFile) import qualified StmContainers.Map as STM import qualified System.Directory as Dir import qualified System.FilePath.Glob as Glob +import Development.IDE.Core.InputPath (InputPath (InputPath)) +import Development.IDE.Graph.Internal.Rules (InputClass(AllHaskellFiles)) {- Note [File existence cache and LSP file watchers] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -133,7 +135,7 @@ fromChange FileChangeType_Changed = Nothing ------------------------------------------------------------------------------------- -- | Returns True if the file exists -getFileExists :: NormalizedFilePath -> Action Bool +getFileExists :: InputPath AllHaskellFiles -> Action Bool getFileExists fp = use_ GetFileExists fp {- Note [Which files should we watch?] @@ -192,12 +194,15 @@ fileExistsRules recorder lspEnv = do then fileExistsRulesFast recorder isWatched else fileExistsRulesSlow recorder - fileStoreRules (cmapWithPrio LogFileStore recorder) isWatched + fileStoreRules (cmapWithPrio LogFileStore recorder) (\(InputPath f) -> isWatched f) -- Requires an lsp client that provides WatchedFiles notifications, but assumes that this has already been checked. fileExistsRulesFast :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules () fileExistsRulesFast recorder isWatched = - defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \GetFileExists file -> do + defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics runGetFileExists + where + runGetFileExists :: GetFileExists -> InputPath AllHaskellFiles -> Action (Maybe BS.ByteString, Maybe Bool) + runGetFileExists GetFileExists (InputPath file) = do isWF <- isWatched file if isWF then fileExistsFast file @@ -238,7 +243,10 @@ summarizeExists x = Just $ if x then BS.singleton 1 else BS.empty fileExistsRulesSlow :: Recorder (WithPriority Log) -> Rules () fileExistsRulesSlow recorder = - defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \GetFileExists file -> fileExistsSlow file + defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics runGetFileExists + where + runGetFileExists :: GetFileExists -> InputPath AllHaskellFiles -> Action (Maybe BS.ByteString, Maybe Bool) + runGetFileExists GetFileExists (InputPath file) = fileExistsSlow file fileExistsSlow :: NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool) fileExistsSlow file = do diff --git a/ghcide/src/Development/IDE/Core/FileStore.hs b/ghcide/src/Development/IDE/Core/FileStore.hs index 6c0cb875b0..95d4fd72e3 100644 --- a/ghcide/src/Development/IDE/Core/FileStore.hs +++ b/ghcide/src/Development/IDE/Core/FileStore.hs @@ -1,5 +1,6 @@ -- Copyright (c) 2019 The DAML Authors. All rights reserved. -- SPDX-License-Identifier: Apache-2.0 +{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE TypeFamilies #-} module Development.IDE.Core.FileStore( @@ -69,6 +70,8 @@ import Language.LSP.VFS import System.FilePath import System.IO.Error import System.IO.Unsafe +import Development.IDE.Core.InputPath (InputPath (unInputPath), classifyProjectHaskellInputs) +import Development.IDE.Graph.Internal.Rules (InputClass(AllHaskellFiles)) data Log @@ -88,31 +91,34 @@ instance Pretty Log where <+> pretty (fmap (fmap show) reverseDepPaths) LogShake msg -> pretty msg -addWatchedFileRule :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules () +addWatchedFileRule :: Recorder (WithPriority Log) -> (InputPath AllHaskellFiles -> Action Bool) -> Rules () addWatchedFileRule recorder isWatched = defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \AddWatchedFile f -> do isAlreadyWatched <- isWatched f - isWp <- isWorkspaceFile f + isWp <- isWorkspaceFile $ unInputPath f if isAlreadyWatched then pure (Just True) else if not isWp then pure (Just False) else do ShakeExtras{lspEnv} <- getShakeExtras case lspEnv of Just env -> fmap Just $ liftIO $ LSP.runLspT env $ - registerFileWatches [fromNormalizedFilePath f] + registerFileWatches [fromNormalizedFilePath (unInputPath f)] Nothing -> pure $ Just False getModificationTimeRule :: Recorder (WithPriority Log) -> Rules () -getModificationTimeRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \(GetModificationTime_ missingFileDiags) file -> - getModificationTimeImpl missingFileDiags file +getModificationTimeRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule runGetModificationTimeImpl + where + runGetModificationTimeImpl :: GetModificationTime -> InputPath AllHaskellFiles -> Action (Maybe BS.ByteString, ([FileDiagnostic], Maybe FileVersion)) + runGetModificationTimeImpl (GetModificationTime_ missingFileDiags) input = + getModificationTimeImpl missingFileDiags input getModificationTimeImpl :: Bool - -> NormalizedFilePath + -> InputPath AllHaskellFiles -> Action (Maybe BS.ByteString, ([FileDiagnostic], Maybe FileVersion)) getModificationTimeImpl missingFileDiags file = do - let file' = fromNormalizedFilePath file + let file' = fromNormalizedFilePath $ unInputPath file let wrap time = (Just $ LBS.toStrict $ B.encode $ toRational time, ([], Just $ ModificationTime time)) - mbVf <- getVirtualFile file + mbVf <- getVirtualFile $ unInputPath file case mbVf of Just (virtualFileVersion -> ver) -> do alwaysRerun @@ -124,7 +130,7 @@ getModificationTimeImpl missingFileDiags file = do -- but also need a dependency on IsFileOfInterest to reinstall -- alwaysRerun when the file becomes VFS void (use_ IsFileOfInterest file) - else if isInterface file + else if isInterface (unInputPath file) then -- interface files are tracked specially using the closed world assumption pure () else -- in all other cases we will need to freshly check the file system @@ -134,7 +140,7 @@ getModificationTimeImpl missingFileDiags file = do `catch` \(e :: IOException) -> do let err | isDoesNotExistError e = "File does not exist: " ++ file' | otherwise = "IO error while reading " ++ file' ++ ", " ++ displayException e - diag = ideErrorText file (T.pack err) + diag = ideErrorText (unInputPath file) (T.pack err) if isDoesNotExistError e && not missingFileDiags then return (Nothing, ([], Nothing)) else return (Nothing, ([diag], Nothing)) @@ -171,22 +177,25 @@ modificationTime VFSVersion{} = Nothing modificationTime (ModificationTime posix) = Just $ posixSecondsToUTCTime posix getFileContentsRule :: Recorder (WithPriority Log) -> Rules () -getFileContentsRule recorder = define (cmapWithPrio LogShake recorder) $ \GetFileContents file -> getFileContentsImpl file +getFileContentsRule recorder = define (cmapWithPrio LogShake recorder) runGetFileContentsImpl + where + runGetFileContentsImpl :: GetFileContents -> InputPath AllHaskellFiles -> Action ([FileDiagnostic], Maybe (FileVersion, Maybe T.Text)) + runGetFileContentsImpl GetFileContents input = getFileContentsImpl input getFileContentsImpl - :: NormalizedFilePath + :: InputPath AllHaskellFiles -> Action ([FileDiagnostic], Maybe (FileVersion, Maybe T.Text)) getFileContentsImpl file = do -- need to depend on modification time to introduce a dependency with Cutoff time <- use_ GetModificationTime file res <- do - mbVirtual <- getVirtualFile file + mbVirtual <- getVirtualFile $ unInputPath file pure $ virtualFileText <$> mbVirtual pure ([], Just (time, res)) -- | Returns the modification time and the contents. -- For VFS paths, the modification time is the current time. -getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe T.Text) +getFileContents :: InputPath AllHaskellFiles -> Action (UTCTime, Maybe T.Text) getFileContents f = do (fv, txt) <- use_ GetFileContents f modTime <- case modificationTime fv of @@ -196,11 +205,11 @@ getFileContents f = do liftIO $ case foi of IsFOI Modified{} -> getCurrentTime _ -> do - posix <- getModTime $ fromNormalizedFilePath f + posix <- getModTime $ fromNormalizedFilePath $ unInputPath f pure $ posixSecondsToUTCTime posix return (modTime, txt) -fileStoreRules :: Recorder (WithPriority Log) -> (NormalizedFilePath -> Action Bool) -> Rules () +fileStoreRules :: Recorder (WithPriority Log) -> (InputPath AllHaskellFiles -> Action Bool) -> Rules () fileStoreRules recorder isWatched = do getModificationTimeRule recorder getFileContentsRule recorder @@ -239,7 +248,8 @@ typecheckParentsAction recorder nfp = do Nothing -> logWith recorder Info $ LogCouldNotIdentifyReverseDeps nfp Just rs -> do logWith recorder Info $ LogTypeCheckingReverseDeps nfp revs - void $ uses GetModIface rs + let classifiedInputs = classifyProjectHaskellInputs rs + void $ uses GetModIface classifiedInputs -- | Note that some keys have been modified and restart the session -- Only valid if the virtual file system was initialised by LSP, as that diff --git a/ghcide/src/Development/IDE/Core/InputPath.hs b/ghcide/src/Development/IDE/Core/InputPath.hs new file mode 100644 index 0000000000..602c0c65d4 --- /dev/null +++ b/ghcide/src/Development/IDE/Core/InputPath.hs @@ -0,0 +1,46 @@ +{-# LANGUAGE DerivingStrategies #-} + +module Development.IDE.Core.InputPath where + +import Control.DeepSeq +import Data.Hashable +import Data.List (isInfixOf) +import Data.Typeable +import Development.IDE.Graph.Internal.Rules (InputClass(..)) +import Language.LSP.Protocol.Types (NormalizedFilePath, fromNormalizedFilePath) +import System.FilePath (splitDirectories) + +newtype InputPath (i :: InputClass) = + InputPath { unInputPath :: NormalizedFilePath } + deriving newtype (Eq, Hashable, NFData, Typeable, Show) + +-- All Haskell files are valid, and we assume all +-- files are Haskell files (for now) so there is +-- no need to filter out any FilePaths. +classifyAllHaskellInputs :: [NormalizedFilePath] -> [InputPath AllHaskellFiles] +classifyAllHaskellInputs = map InputPath + +-- Dependency files should not be considered +-- ProjectHaskellFiles, so we filter them out +-- before classifying all other files as +-- ProjectHaskellFiles. +classifyProjectHaskellInputs :: [NormalizedFilePath] -> [InputPath ProjectHaskellFiles] +classifyProjectHaskellInputs = foldr classifyInputPath [] + where + classifyInputPath :: NormalizedFilePath -> [InputPath ProjectHaskellFiles] -> [InputPath ProjectHaskellFiles] + classifyInputPath nfp projectInputs = + case dependencyDirectory `isInfixOf` rawInput of + -- The input is a dependency, so don't include + -- it in the project inputs. + True -> projectInputs + -- The input is not a depencency, so include it + -- in the project inputs + False -> InputPath nfp : projectInputs + where + dependencyDirectory :: [FilePath] + dependencyDirectory = [".hls", "dependencies"] + rawInput :: [FilePath] + rawInput = splitDirectories (fromNormalizedFilePath nfp) + +generalizeProjectInput :: InputPath ProjectHaskellFiles -> InputPath AllHaskellFiles +generalizeProjectInput = InputPath . unInputPath diff --git a/ghcide/src/Development/IDE/Core/OfInterest.hs b/ghcide/src/Development/IDE/Core/OfInterest.hs index 2a594c1021..8151572350 100644 --- a/ghcide/src/Development/IDE/Core/OfInterest.hs +++ b/ghcide/src/Development/IDE/Core/OfInterest.hs @@ -50,6 +50,7 @@ import Ide.Logger (Pretty (pretty), logWith) import qualified Language.LSP.Protocol.Message as LSP import qualified Language.LSP.Server as LSP +import Development.IDE.Core.InputPath (classifyProjectHaskellInputs, classifyAllHaskellInputs, InputPath (unInputPath)) data Log = LogShake Shake.Log deriving Show @@ -67,10 +68,11 @@ ofInterestRules :: Recorder (WithPriority Log) -> Rules () ofInterestRules recorder = do addIdeGlobal . OfInterestVar =<< liftIO (newVar HashMap.empty) addIdeGlobal . GarbageCollectVar =<< liftIO (newVar False) - defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \IsFileOfInterest f -> do + defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \IsFileOfInterest input -> do alwaysRerun filesOfInterest <- getFilesOfInterestUntracked - let foi = maybe NotFOI IsFOI $ f `HashMap.lookup` filesOfInterest + let rawFile = unInputPath input + let foi = maybe NotFOI IsFOI $ rawFile `HashMap.lookup` filesOfInterest fp = summarize foi res = (Just fp, Just foi) return res @@ -134,6 +136,8 @@ scheduleGarbageCollection state = do kick :: Action () kick = do files <- HashMap.keys <$> getFilesOfInterestUntracked + let classifiedHaskellFiles = classifyAllHaskellInputs files + classifiedProjectFiles = classifyProjectHaskellInputs files ShakeExtras{exportsMap, ideTesting = IdeTesting testing, lspEnv, progress} <- getShakeExtras let signal :: KnownSymbol s => Proxy s -> Action () signal msg = when testing $ liftIO $ @@ -145,11 +149,11 @@ kick = do liftIO $ progressUpdate progress ProgressNewStarted -- Update the exports map - results <- uses GenerateCore files - <* uses GetHieAst files + results <- uses GenerateCore classifiedProjectFiles + <* uses GetHieAst classifiedHaskellFiles -- needed to have non local completions on the first edit -- when the first edit breaks the module header - <* uses NonLocalCompletions files + <* uses NonLocalCompletions classifiedProjectFiles let mguts = catMaybes results void $ liftIO $ atomically $ modifyTVar' exportsMap (updateExportsMapMg mguts) diff --git a/ghcide/src/Development/IDE/Core/PluginUtils.hs b/ghcide/src/Development/IDE/Core/PluginUtils.hs index 76c88421c9..d0335f01dd 100644 --- a/ghcide/src/Development/IDE/Core/PluginUtils.hs +++ b/ghcide/src/Development/IDE/Core/PluginUtils.hs @@ -40,11 +40,11 @@ import Development.IDE.Core.Shake (IdeAction, IdeRule, import qualified Development.IDE.Core.Shake as Shake import Development.IDE.GHC.Orphans () import Development.IDE.Graph hiding (ShakeValue) -import Development.IDE.Types.Location (NormalizedFilePath) import qualified Development.IDE.Types.Location as Location import qualified Ide.Logger as Logger import Ide.Plugin.Error import qualified Language.LSP.Protocol.Types as LSP +import Development.IDE.Core.InputPath (InputPath) -- ---------------------------------------------------------------------------- -- Action wrappers @@ -63,30 +63,30 @@ runActionMT herald ide act = join $ shakeEnqueue (shakeExtras ide) (mkDelayedAction herald Logger.Debug $ runMaybeT act) -- |ExceptT version of `use` that throws a PluginRuleFailed upon failure -useE :: IdeRule k v => k -> NormalizedFilePath -> ExceptT PluginError Action v +useE :: IdeRule k i v => k -> InputPath i -> ExceptT PluginError Action v useE k = maybeToExceptT (PluginRuleFailed (T.pack $ show k)) . useMT k -- |MaybeT version of `use` -useMT :: IdeRule k v => k -> NormalizedFilePath -> MaybeT Action v +useMT :: IdeRule k i v => k -> InputPath i -> MaybeT Action v useMT k = MaybeT . Shake.use k -- |ExceptT version of `uses` that throws a PluginRuleFailed upon failure -usesE :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> ExceptT PluginError Action (f v) +usesE :: (Traversable f, IdeRule k i v) => k -> f (InputPath i) -> ExceptT PluginError Action (f v) usesE k = maybeToExceptT (PluginRuleFailed (T.pack $ show k)) . usesMT k -- |MaybeT version of `uses` -usesMT :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> MaybeT Action (f v) +usesMT :: (Traversable f, IdeRule k i v) => k -> f (InputPath i) -> MaybeT Action (f v) usesMT k xs = MaybeT $ sequence <$> Shake.uses k xs -- |ExceptT version of `useWithStale` that throws a PluginRuleFailed upon -- failure -useWithStaleE :: IdeRule k v - => k -> NormalizedFilePath -> ExceptT PluginError Action (v, PositionMapping) +useWithStaleE :: IdeRule k i v + => k -> InputPath i -> ExceptT PluginError Action (v, PositionMapping) useWithStaleE key = maybeToExceptT (PluginRuleFailed (T.pack $ show key)) . useWithStaleMT key -- |MaybeT version of `useWithStale` -useWithStaleMT :: IdeRule k v - => k -> NormalizedFilePath -> MaybeT Action (v, PositionMapping) +useWithStaleMT :: IdeRule k i v + => k -> InputPath i -> MaybeT Action (v, PositionMapping) useWithStaleMT key file = MaybeT $ runIdentity <$> Shake.usesWithStale key (Identity file) -- ---------------------------------------------------------------------------- @@ -103,11 +103,11 @@ runIdeActionMT _herald s i = MaybeT $ liftIO $ runReaderT (Shake.runIdeActionT $ -- |ExceptT version of `useWithStaleFast` that throws a PluginRuleFailed upon -- failure -useWithStaleFastE :: IdeRule k v => k -> NormalizedFilePath -> ExceptT PluginError IdeAction (v, PositionMapping) +useWithStaleFastE :: IdeRule k i v => k -> InputPath i -> ExceptT PluginError IdeAction (v, PositionMapping) useWithStaleFastE k = maybeToExceptT (PluginRuleFailed (T.pack $ show k)) . useWithStaleFastMT k -- |MaybeT version of `useWithStaleFast` -useWithStaleFastMT :: IdeRule k v => k -> NormalizedFilePath -> MaybeT IdeAction (v, PositionMapping) +useWithStaleFastMT :: IdeRule k i v => k -> InputPath i -> MaybeT IdeAction (v, PositionMapping) useWithStaleFastMT k = MaybeT . Shake.useWithStaleFast k -- ---------------------------------------------------------------------------- diff --git a/ghcide/src/Development/IDE/Core/RuleTypes.hs b/ghcide/src/Development/IDE/Core/RuleTypes.hs index 3d60669f5c..cd08b7741c 100644 --- a/ghcide/src/Development/IDE/Core/RuleTypes.hs +++ b/ghcide/src/Development/IDE/Core/RuleTypes.hs @@ -29,6 +29,7 @@ import Development.IDE.GHC.Compat.Util import Development.IDE.GHC.CoreFile import Development.IDE.GHC.Util import Development.IDE.Graph +import Development.IDE.Graph.Internal.Rules (InputClass(..)) import Development.IDE.Import.DependencyInformation import Development.IDE.Types.HscEnvEq (HscEnvEq) import Development.IDE.Types.KnownTargets @@ -65,21 +66,26 @@ encodeLinkableType (Just ObjectLinkable) = "2" -- | The parse tree for the file using GetFileContents type instance RuleResult GetParsedModule = ParsedModule +type instance RuleInput GetParsedModule = ProjectHaskellFiles -- | The parse tree for the file using GetFileContents, -- all comments included using Opt_KeepRawTokenStream type instance RuleResult GetParsedModuleWithComments = ParsedModule +type instance RuleInput GetParsedModuleWithComments = ProjectHaskellFiles type instance RuleResult GetModuleGraph = DependencyInformation +type instance RuleInput GetModuleGraph = NoFile data GetKnownTargets = GetKnownTargets deriving (Show, Generic, Eq, Ord) instance Hashable GetKnownTargets instance NFData GetKnownTargets type instance RuleResult GetKnownTargets = KnownTargets +type instance RuleInput GetKnownTargets = NoFile -- | Convert to Core, requires TypeCheck* type instance RuleResult GenerateCore = ModGuts +type instance RuleInput GenerateCore = ProjectHaskellFiles data GenerateCore = GenerateCore deriving (Eq, Show, Typeable, Generic) @@ -87,6 +93,7 @@ instance Hashable GenerateCore instance NFData GenerateCore type instance RuleResult GetLinkable = LinkableResult +type instance RuleInput GetLinkable = ProjectHaskellFiles data LinkableResult = LinkableResult @@ -112,6 +119,7 @@ instance Hashable GetImportMap instance NFData GetImportMap type instance RuleResult GetImportMap = ImportMap +type instance RuleInput GetImportMap = ProjectHaskellFiles newtype ImportMap = ImportMap { importMap :: M.Map ModuleName NormalizedFilePath -- ^ Where are the modules imported by this file located? } deriving stock Show @@ -232,12 +240,15 @@ instance Show HieAstResult where -- | The type checked version of this file, requires TypeCheck+ type instance RuleResult TypeCheck = TcModuleResult +type instance RuleInput TypeCheck = ProjectHaskellFiles -- | The uncompressed HieAST type instance RuleResult GetHieAst = HieAstResult +type instance RuleInput GetHieAst = AllHaskellFiles -- | A IntervalMap telling us what is in scope at each point type instance RuleResult GetBindings = Bindings +type instance RuleInput GetBindings = ProjectHaskellFiles data DocAndTyThingMap = DKMap {getDocMap :: !DocMap, getTyThingMap :: !TyThingMap} instance NFData DocAndTyThingMap where @@ -247,39 +258,50 @@ instance Show DocAndTyThingMap where show = const "docmap" type instance RuleResult GetDocMap = DocAndTyThingMap +type instance RuleInput GetDocMap = ProjectHaskellFiles -- | A GHC session that we reuse. type instance RuleResult GhcSession = HscEnvEq +type instance RuleInput GhcSession = ProjectHaskellFiles -- | A GHC session preloaded with all the dependencies -- This rule is also responsible for calling ReportImportCycles for the direct dependencies type instance RuleResult GhcSessionDeps = HscEnvEq +type instance RuleInput GhcSessionDeps = ProjectHaskellFiles -- | Resolve the imports in a module to the file path of a module in the same package type instance RuleResult GetLocatedImports = [(Located ModuleName, Maybe ArtifactsLocation)] +type instance RuleInput GetLocatedImports = ProjectHaskellFiles -- | This rule is used to report import cycles. It depends on GetModuleGraph. -- We cannot report the cycles directly from GetModuleGraph since -- we can only report diagnostics for the current file. type instance RuleResult ReportImportCycles = () +type instance RuleInput ReportImportCycles = ProjectHaskellFiles -- | Read the module interface file from disk. Throws an error for VFS files. -- This is an internal rule, use 'GetModIface' instead. type instance RuleResult GetModIfaceFromDisk = HiFileResult +type instance RuleInput GetModIfaceFromDisk = ProjectHaskellFiles -- | GetModIfaceFromDisk and index the `.hie` file into the database. -- This is an internal rule, use 'GetModIface' instead. type instance RuleResult GetModIfaceFromDiskAndIndex = HiFileResult +type instance RuleInput GetModIfaceFromDiskAndIndex = ProjectHaskellFiles -- | Get a module interface details, either from an interface file or a typechecked module type instance RuleResult GetModIface = HiFileResult +type instance RuleInput GetModIface = ProjectHaskellFiles -- | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk. type instance RuleResult GetFileContents = (FileVersion, Maybe Text) +type instance RuleInput GetFileContents = AllHaskellFiles type instance RuleResult GetFileExists = Bool +type instance RuleInput GetFileExists = AllHaskellFiles type instance RuleResult AddWatchedFile = Bool +type instance RuleInput AddWatchedFile = AllHaskellFiles -- The Shake key type for getModificationTime queries @@ -309,6 +331,7 @@ pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True} -- | Get the modification time of a file. type instance RuleResult GetModificationTime = FileVersion +type instance RuleInput GetModificationTime = AllHaskellFiles -- | Either the mtime from disk or an LSP version -- LSP versions always compare as greater than on disk versions @@ -351,6 +374,7 @@ instance Hashable IsFileOfInterestResult instance NFData IsFileOfInterestResult type instance RuleResult IsFileOfInterest = IsFileOfInterestResult +type instance RuleInput IsFileOfInterest = AllHaskellFiles data ModSummaryResult = ModSummaryResult { msrModSummary :: !ModSummary @@ -373,9 +397,11 @@ instance NFData ModSummaryResult where -- | Generate a ModSummary that has enough information to be used to get .hi and .hie files. -- without needing to parse the entire source type instance RuleResult GetModSummary = ModSummaryResult +type instance RuleInput GetModSummary = ProjectHaskellFiles -- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult +type instance RuleInput GetModSummaryWithoutTimestamps = ProjectHaskellFiles data GetParsedModule = GetParsedModule deriving (Eq, Show, Typeable, Generic) @@ -394,6 +420,7 @@ instance NFData GetLocatedImports -- | Does this module need to be compiled? type instance RuleResult NeedsCompilation = Maybe LinkableType +type instance RuleInput NeedsCompilation = ProjectHaskellFiles data NeedsCompilation = NeedsCompilation deriving (Eq, Show, Typeable, Generic) @@ -487,6 +514,7 @@ instance Hashable GetClientSettings instance NFData GetClientSettings type instance RuleResult GetClientSettings = Hashed (Maybe Value) +type instance RuleInput GetClientSettings = NoFile data AddWatchedFile = AddWatchedFile deriving (Eq, Show, Typeable, Generic) instance Hashable AddWatchedFile @@ -497,6 +525,7 @@ instance NFData AddWatchedFile -- thread killed exception issues, so we lift it to a full rule. -- https://github.com/digital-asset/daml/pull/2808#issuecomment-529639547 type instance RuleResult GhcSessionIO = IdeGhcSession +type instance RuleInput GhcSessionIO = NoFile data IdeGhcSession = IdeGhcSession { loadSessionFun :: FilePath -> IO (IdeResult HscEnvEq, [FilePath]) diff --git a/ghcide/src/Development/IDE/Core/Rules.hs b/ghcide/src/Development/IDE/Core/Rules.hs index b0d61579cc..c7c2558e49 100644 --- a/ghcide/src/Development/IDE/Core/Rules.hs +++ b/ghcide/src/Development/IDE/Core/Rules.hs @@ -101,6 +101,7 @@ import Development.IDE.Core.FileExists hiding (Log, import Development.IDE.Core.FileStore (getFileContents, getModTime) import Development.IDE.Core.IdeConfiguration +import Development.IDE.Core.InputPath import Development.IDE.Core.OfInterest hiding (Log, LogShake) import Development.IDE.Core.PositionMapping @@ -169,6 +170,7 @@ import System.Info.Extra (isWindows) import qualified Data.IntMap as IM import GHC.Fingerprint +import Development.IDE.Graph.Internal.Rules (InputClass(ProjectHaskellFiles)) data Log @@ -220,18 +222,18 @@ toIdeResult = either (, Nothing) (([],) . Just) -- TODO: return text --> return rope getSourceFileSource :: NormalizedFilePath -> Action BS.ByteString getSourceFileSource nfp = do - (_, msource) <- getFileContents nfp + (_, msource) <- getFileContents $ InputPath nfp case msource of Nothing -> liftIO $ BS.readFile (fromNormalizedFilePath nfp) Just source -> pure $ T.encodeUtf8 source -- | Parse the contents of a haskell file. -getParsedModule :: NormalizedFilePath -> Action (Maybe ParsedModule) +getParsedModule :: InputPath ProjectHaskellFiles -> Action (Maybe ParsedModule) getParsedModule = use GetParsedModule -- | Parse the contents of a haskell file, -- ensuring comments are preserved in annotations -getParsedModuleWithComments :: NormalizedFilePath -> Action (Maybe ParsedModule) +getParsedModuleWithComments :: InputPath ProjectHaskellFiles -> Action (Maybe ParsedModule) getParsedModuleWithComments = use GetParsedModuleWithComments ------------------------------------------------------------ @@ -259,7 +261,7 @@ getParsedModuleRule recorder = -- We still parse with Haddocks whether Opt_Haddock is True or False to collect information -- but we no longer need to parse with and without Haddocks separately for above GHC90. - liftIO $ (fmap.fmap.fmap) reset_ms $ getParsedModuleDefinition hsc opt file (withOptHaddock ms) + liftIO $ (fmap.fmap.fmap) reset_ms $ getParsedModuleDefinition hsc opt (unInputPath file) (withOptHaddock ms) withOptHaddock :: ModSummary -> ModSummary withOptHaddock = withOption Opt_Haddock @@ -286,7 +288,7 @@ getParsedModuleWithCommentsRule recorder = let ms'' = ms' { ms_hspp_opts = modify_dflags $ ms_hspp_opts ms' } reset_ms pm = pm { pm_mod_summary = ms' } - liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition hsc opt file ms'' + liftIO $ fmap (fmap reset_ms) $ snd <$> getParsedModuleDefinition hsc opt (unInputPath file) ms'' getModifyDynFlags :: (DynFlagsModifications -> a) -> Action a getModifyDynFlags f = do @@ -321,16 +323,16 @@ getLocatedImportsRule recorder = let getTargetFor modName nfp | Just (TargetFile nfp') <- HM.lookup (TargetFile nfp) targetsMap = do -- reuse the existing NormalizedFilePath in order to maximize sharing - itExists <- getFileExists nfp' + itExists <- getFileExists $ InputPath nfp' return $ if itExists then Just nfp' else Nothing | Just tt <- HM.lookup (TargetModule modName) targets = do -- reuse the existing NormalizedFilePath in order to maximize sharing let ttmap = HM.mapWithKey const (HashSet.toMap tt) nfp' = HM.lookupDefault nfp nfp ttmap - itExists <- getFileExists nfp' + itExists <- getFileExists $ InputPath nfp' return $ if itExists then Just nfp' else Nothing | otherwise = do - itExists <- getFileExists nfp + itExists <- getFileExists $ InputPath nfp return $ if itExists then Just nfp else Nothing (diags, imports') <- fmap unzip $ forM imports $ \(isSource, (mbPkgName, modName)) -> do diagOrImp <- locateModule (hscSetFlags dflags env) import_dirs (optExtensions opt) getTargetFor modName mbPkgName isSource @@ -367,7 +369,7 @@ execRawDepM act = -- | Given a target file path, construct the raw dependency results by following -- imports recursively. -rawDependencyInformation :: [NormalizedFilePath] -> Action (RawDependencyInformation, BootIdMap) +rawDependencyInformation :: [InputPath ProjectHaskellFiles] -> Action (RawDependencyInformation, BootIdMap) rawDependencyInformation fs = do (rdi, ss) <- execRawDepM (goPlural fs) let bm = IntMap.foldrWithKey (updateBootMap rdi) IntMap.empty ss @@ -377,15 +379,15 @@ rawDependencyInformation fs = do mss <- lift $ (fmap.fmap) msrModSummary <$> uses GetModSummaryWithoutTimestamps ff zipWithM go ff mss - go :: NormalizedFilePath -- ^ Current module being processed + go :: InputPath ProjectHaskellFiles -- ^ Current module being processed -> Maybe ModSummary -- ^ ModSummary of the module -> RawDepM FilePathId go f mbModSum = do -- First check to see if we have already processed the FilePath -- If we have, just return its Id but don't update any of the state. -- Otherwise, we need to process its imports. - checkAlreadyProcessed f $ do - let al = modSummaryToArtifactsLocation f mbModSum + checkAlreadyProcessed (unInputPath f) $ do + let al = modSummaryToArtifactsLocation (unInputPath f) mbModSum -- Get a fresh FilePathId for the new file fId <- getFreshFid al -- Record this module and its location @@ -412,7 +414,7 @@ rawDependencyInformation fs = do (mns, ls) = unzip with_file -- Recursively process all the imports we just learnt about -- and get back a list of their FilePathIds - fids <- goPlural $ map artifactFilePath ls + fids <- goPlural $ (classifyProjectHaskellInputs . map artifactFilePath) ls -- Associate together the ModuleName with the FilePathId let moduleImports' = map (,Nothing) no_file ++ zip mns (map Just fids) -- Insert into the map the information about this modules @@ -468,7 +470,7 @@ reportImportCyclesRule :: Recorder (WithPriority Log) -> Rules () reportImportCyclesRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \ReportImportCycles file -> fmap (\errs -> if null errs then (Just "1",([], Just ())) else (Nothing, (errs, Nothing))) $ do DependencyInformation{..} <- useNoFile_ GetModuleGraph - case pathToId depPathIdMap file of + case pathToId depPathIdMap (unInputPath file) of -- The header of the file does not parse, so it can't be part of any import cycles. Nothing -> pure [] Just fileId -> @@ -479,7 +481,7 @@ reportImportCyclesRule recorder = -- Convert cycles of files into cycles of module names forM cycles $ \(imp, files) -> do modNames <- forM files $ - getModuleName . idToPath depPathIdMap + getModuleName . InputPath . idToPath depPathIdMap pure $ toDiag imp $ sort modNames where cycleErrorInFile f (PartOfCycle imp fs) | f `elem` fs = Just (imp, fs) @@ -504,10 +506,37 @@ reportImportCyclesRule recorder = getHieAstsRule :: Recorder (WithPriority Log) -> Rules () getHieAstsRule recorder = - define (cmapWithPrio LogShake recorder) $ \GetHieAst f -> do - tmr <- use_ TypeCheck f - hsc <- hscEnv <$> use_ GhcSessionDeps f - getHieAstRuleDefinition f hsc tmr + define (cmapWithPrio LogShake recorder) $ \GetHieAst input -> do + let file = unInputPath input + case classifyProjectHaskellInputs [file] of + [] -> do + se <- getShakeExtras + mHieFile <- liftIO + $ runIdeAction "GetHieAst" se + $ runMaybeT + -- We can look up the HIE file from its source + -- because at this point lookupMod has already been + -- called and has created the the source file in + -- the .hls directory and indexed it. + $ readHieFileForSrcFromDisk recorder file + pure ([], makeHieAstResult <$> mHieFile) + projectInput:_ -> do + tmr <- use_ TypeCheck projectInput + hsc <- hscEnv <$> use_ GhcSessionDeps projectInput + getHieAstRuleDefinition projectInput hsc tmr + where + -- Make an HieAstResult from a loaded HieFile + makeHieAstResult :: HieFile -> HieAstResult + makeHieAstResult hieFile = + HAR + (hie_module hieFile) + hieAsts + (generateReferencesMap $ M.elems $ getAsts hieAsts) + mempty + (HieFromDisk hieFile) + where + hieAsts :: HieASTs TypeIndex + hieAsts = hie_asts hieFile persistentHieFileRule :: Recorder (WithPriority Log) -> Rules () persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybeT $ do @@ -521,23 +550,24 @@ persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybe del = deltaFromDiff (T.decodeUtf8 $ Compat.hie_hs_src res) currentSource pure (HAR (Compat.hie_module res) (Compat.hie_asts res) refmap mempty (HieFromDisk res),del,ver) -getHieAstRuleDefinition :: NormalizedFilePath -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult) -getHieAstRuleDefinition f hsc tmr = do +getHieAstRuleDefinition :: InputPath ProjectHaskellFiles -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult) +getHieAstRuleDefinition input hsc tmr = do + let file = unInputPath input (diags, masts) <- liftIO $ generateHieAsts hsc tmr se <- getShakeExtras - isFoi <- use_ IsFileOfInterest f + isFoi <- use_ IsFileOfInterest $ generalizeProjectInput input diagsWrite <- case isFoi of IsFOI Modified{firstOpen = False} -> do when (coerce $ ideTesting se) $ liftIO $ mRunLspT (lspEnv se) $ LSP.sendNotification (SMethod_CustomMethod (Proxy @"ghcide/reference/ready")) $ - toJSON $ fromNormalizedFilePath f + toJSON $ fromNormalizedFilePath file pure [] _ | Just asts <- masts -> do - source <- getSourceFileSource f + source <- getSourceFileSource file let exports = tcg_exports $ tmrTypechecked tmr modSummary = tmrModSummary tmr - liftIO $ writeAndIndexHieFile hsc se modSummary f exports asts source + liftIO $ writeAndIndexHieFile hsc se modSummary file exports asts source _ -> pure [] let refmap = Compat.generateReferencesMap . Compat.getAsts <$> masts @@ -557,7 +587,7 @@ persistentImportMapRule = addPersistentRule GetImportMap $ \_ -> pure $ Just (Im getBindingsRule :: Recorder (WithPriority Log) -> Rules () getBindingsRule recorder = define (cmapWithPrio LogShake recorder) $ \GetBindings f -> do - HAR{hieKind=kind, refMap=rm} <- use_ GetHieAst f + HAR{hieKind=kind, refMap=rm} <- use_ GetHieAst $ generalizeProjectInput f case kind of HieFresh -> pure ([], Just $ bindings rm) HieFromDisk _ -> pure ([], Nothing) @@ -569,7 +599,7 @@ getDocMapRule recorder = -- but we never generated a DocMap for it (tmrTypechecked -> tc, _) <- useWithStale_ TypeCheck file (hscEnv -> hsc, _) <- useWithStale_ GhcSessionDeps file - (HAR{refMap=rf}, _) <- useWithStale_ GetHieAst file + (HAR{refMap=rf}, _) <- useWithStale_ GetHieAst $ generalizeProjectInput file dkMap <- liftIO $ mkDocMap hsc rf tc return ([],Just dkMap) @@ -600,12 +630,12 @@ typeCheckRule :: Recorder (WithPriority Log) -> Rules () typeCheckRule recorder = define (cmapWithPrio LogShake recorder) $ \TypeCheck file -> do pm <- use_ GetParsedModule file hsc <- hscEnv <$> use_ GhcSessionDeps file - foi <- use_ IsFileOfInterest file + foi <- use_ IsFileOfInterest $ generalizeProjectInput file -- We should only call the typecheck rule for files of interest. -- Keeping typechecked modules in memory for other files is -- very expensive. when (foi == NotFOI) $ - logWith recorder Logger.Warning $ LogTypecheckedFOI file + logWith recorder Logger.Warning $ LogTypecheckedFOI $ unInputPath file typeCheckRuleDefinition hsc pm knownFilesRule :: Recorder (WithPriority Log) -> Rules () @@ -617,13 +647,13 @@ knownFilesRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorde getModuleGraphRule :: Recorder (WithPriority Log) -> Rules () getModuleGraphRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorder) $ \GetModuleGraph -> do fs <- toKnownFiles <$> useNoFile_ GetKnownTargets - dependencyInfoForFiles (HashSet.toList fs) + dependencyInfoForFiles (map (InputPath @ProjectHaskellFiles) $ HashSet.toList fs) -dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation) +dependencyInfoForFiles :: [InputPath ProjectHaskellFiles] -> Action (BS.ByteString, DependencyInformation) dependencyInfoForFiles fs = do (rawDepInfo, bm) <- rawDependencyInformation fs let (all_fs, _all_ids) = unzip $ HM.toList $ pathToIdMap $ rawPathIdMap rawDepInfo - msrs <- uses GetModSummaryWithoutTimestamps all_fs + msrs <- uses GetModSummaryWithoutTimestamps $ classifyProjectHaskellInputs all_fs let mss = map (fmap msrModSummary) msrs let deps = map (\i -> IM.lookup (getFilePathId i) (rawImports rawDepInfo)) _all_ids nodeKeys = IM.fromList $ catMaybes $ zipWith (\fi mms -> (getFilePathId fi,) . NodeKey_Module . msKey <$> mms) _all_ids mss @@ -649,7 +679,7 @@ typeCheckRuleDefinition hsc pm = do unlift <- askUnliftIO let dets = TypecheckHelpers - { getLinkables = unliftIO unlift . uses_ GetLinkable + { getLinkables = unliftIO unlift . uses_ GetLinkable . map InputPath } addUsageDependencies $ liftIO $ typecheckModule defer hsc dets pm @@ -659,7 +689,7 @@ typeCheckRuleDefinition hsc pm = do r@(_, mtc) <- a forM_ mtc $ \tc -> do used_files <- liftIO $ readIORef $ tcg_dependent_files $ tmrTypechecked tc - void $ uses_ GetModificationTime (map toNormalizedFilePath' used_files) + void $ uses_ GetModificationTime (map (InputPath . toNormalizedFilePath') used_files) return r -- | Get all the linkables stored in the graph, i.e. the ones we *do not* need to unload. @@ -695,15 +725,15 @@ 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 + (val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath $ unInputPath file -- add the deps to the Shake graph let addDependency fp = do -- VSCode uses absolute paths in its filewatch notifications let nfp = toNormalizedFilePath' fp - itExists <- getFileExists nfp + itExists <- getFileExists $ InputPath nfp when itExists $ void $ do - use_ GetModificationTime nfp + use_ GetModificationTime $ InputPath nfp mapM_ addDependency deps let cutoffHash = LBS.toStrict $ B.encode (hash (snd val)) @@ -730,21 +760,21 @@ instance Default GhcSessionDepsConfig where ghcSessionDepsDefinition :: -- | full mod summary Bool -> - GhcSessionDepsConfig -> HscEnvEq -> NormalizedFilePath -> Action (Maybe HscEnvEq) -ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do + GhcSessionDepsConfig -> HscEnvEq -> InputPath ProjectHaskellFiles -> Action (Maybe HscEnvEq) +ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env input = do let hsc = hscEnv env - mbdeps <- mapM(fmap artifactFilePath . snd) <$> use_ GetLocatedImports file + mbdeps <- mapM(fmap artifactFilePath . snd) <$> use_ GetLocatedImports input case mbdeps of Nothing -> return Nothing Just deps -> do - when fullModuleGraph $ void $ use_ ReportImportCycles file + when fullModuleGraph $ void $ use_ ReportImportCycles input ms <- msrModSummary <$> if fullModSummary - then use_ GetModSummary file - else use_ GetModSummaryWithoutTimestamps file + then use_ GetModSummary input + else use_ GetModSummaryWithoutTimestamps input - depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps - ifaces <- uses_ GetModIface deps + depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) (map InputPath deps) + ifaces <- uses_ GetModIface $ map InputPath deps let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails emptyHomeModInfoLinkable) ifaces mg <- do if fullModuleGraph @@ -755,7 +785,7 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do -- also points to all the direct descendants of the current module. To get the keys for the descendants -- we must get their `ModSummary`s !final_deps <- do - dep_mss <- map msrModSummary <$> uses_ GetModSummaryWithoutTimestamps deps + dep_mss <- map msrModSummary <$> uses_ GetModSummaryWithoutTimestamps (map InputPath deps) return $!! map (NodeKey_Module . msKey) dep_mss let module_graph_nodes = nubOrdOn mkNodeKey (ModuleNode final_deps ms : concatMap mgModSummaries' mgs) @@ -773,14 +803,14 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do -- | Load a iface from disk, or generate it if there isn't one or it is out of date -- This rule also ensures that the `.hie` and `.o` (if needed) files are written out. getModIfaceFromDiskRule :: Recorder (WithPriority Log) -> Rules () -getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleWithOldValue $ \GetModIfaceFromDisk f old -> do - ms <- msrModSummary <$> use_ GetModSummary f - mb_session <- use GhcSessionDeps f +getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleWithOldValue $ \GetModIfaceFromDisk input old -> do + ms <- msrModSummary <$> use_ GetModSummary input + mb_session <- use GhcSessionDeps input case mb_session of Nothing -> return (Nothing, ([], Nothing)) Just session -> do - linkableType <- getLinkableType f - ver <- use_ GetModificationTime f + linkableType <- getLinkableType input + ver <- use_ GetModificationTime $ generalizeProjectInput input let m_old = case old of Shake.Succeeded (Just old_version) v -> Just (v, old_version) Shake.Stale _ (Just old_version) v -> Just (v, old_version) @@ -788,9 +818,9 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco recompInfo = RecompilationInfo { source_version = ver , old_value = m_old - , get_file_version = use GetModificationTime_{missingFileDiagnostics = False} - , get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface fs - , regenerate = regenerateHiFile session f ms + , get_file_version = use GetModificationTime_{missingFileDiagnostics = False} . InputPath + , get_linkable_hashes = \fs -> map (snd . fromJust . hirCoreFp) <$> uses_ GetModIface (map InputPath fs) + , regenerate = regenerateHiFile session (unInputPath input) ms } r <- loadInterface (hscEnv session) ms linkableType recompInfo case r of @@ -810,15 +840,15 @@ getModIfaceFromDiskRule recorder = defineEarlyCutoff (cmapWithPrio LogShake reco getModIfaceFromDiskAndIndexRule :: Recorder (WithPriority Log) -> Rules () getModIfaceFromDiskAndIndexRule recorder = -- doesn't need early cutoff since all its dependencies already have it - defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetModIfaceFromDiskAndIndex f -> do - x <- use_ GetModIfaceFromDisk f + defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \GetModIfaceFromDiskAndIndex input -> do + x <- use_ GetModIfaceFromDisk input se@ShakeExtras{withHieDb} <- getShakeExtras -- GetModIfaceFromDisk should have written a `.hie` file, must check if it matches version in db let ms = hirModSummary x hie_loc = Compat.ml_hie_file $ ms_location ms fileHash <- liftIO $ Util.getFileHash hie_loc - mrow <- liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb (fromNormalizedFilePath f)) + mrow <- liftIO $ withHieDb (\hieDb -> HieDb.lookupHieFileFromSource hieDb (fromNormalizedFilePath $ unInputPath input)) let hie_loc' = HieDb.hieModuleHieFile <$> mrow case mrow of Just row @@ -828,7 +858,7 @@ getModIfaceFromDiskAndIndexRule recorder = -- All good, the db has indexed the file when (coerce $ ideTesting se) $ liftIO $ mRunLspT (lspEnv se) $ LSP.sendNotification (SMethod_CustomMethod (Proxy @"ghcide/reference/ready")) $ - toJSON $ fromNormalizedFilePath f + toJSON $ fromNormalizedFilePath $ unInputPath input -- Not in db, must re-index _ -> do ehf <- liftIO $ runIdeAction "GetModIfaceFromDiskAndIndex" se $ runExceptT $ @@ -838,8 +868,8 @@ getModIfaceFromDiskAndIndexRule recorder = Left err -> fail $ "failed to read .hie file " ++ show hie_loc ++ ": " ++ displayException err -- can just re-index the file we read from disk Right hf -> liftIO $ do - logWith recorder Logger.Debug $ LogReindexingHieFile f - indexHieFile se ms f fileHash hf + logWith recorder Logger.Debug $ LogReindexingHieFile $ unInputPath input + indexHieFile se ms (unInputPath input) fileHash hf return (Just x) @@ -857,12 +887,12 @@ getModSummaryRule displayTHWarning recorder = do logItOnce <- liftIO $ once $ putStrLn "" addIdeGlobal (DisplayTHWarning logItOnce) - defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModSummary f -> do - session' <- hscEnv <$> use_ GhcSession f + defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModSummary input -> do + session' <- hscEnv <$> use_ GhcSession input modify_dflags <- getModifyDynFlags dynFlagsModifyGlobal let session = hscSetFlags (modify_dflags $ hsc_dflags session') session' - (modTime, mFileContent) <- getFileContents f - let fp = fromNormalizedFilePath f + (modTime, mFileContent) <- getFileContents $ generalizeProjectInput input + let fp = fromNormalizedFilePath $ unInputPath input modS <- liftIO $ runExceptT $ getModSummaryFromImports session fp modTime (textToStringBuffer <$> mFileContent) case modS of @@ -877,8 +907,8 @@ getModSummaryRule displayTHWarning recorder = do return ( Just (fingerprintToBS fingerPrint) , ([], Just res)) Left diags -> return (Nothing, (diags, Nothing)) - defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \GetModSummaryWithoutTimestamps f -> do - mbMs <- use GetModSummary f + defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleNoDiagnostics $ \GetModSummaryWithoutTimestamps input -> do + mbMs <- use GetModSummary input case mbMs of Just res@ModSummaryResult{..} -> do let ms = msrModSummary { @@ -888,10 +918,10 @@ getModSummaryRule displayTHWarning recorder = do return (Just fp, Just res{msrModSummary = ms}) Nothing -> return (Nothing, Nothing) -generateCore :: RunSimplifier -> NormalizedFilePath -> Action (IdeResult ModGuts) -generateCore runSimplifier file = do - packageState <- hscEnv <$> use_ GhcSessionDeps file - tm <- use_ TypeCheck file +generateCore :: RunSimplifier -> InputPath ProjectHaskellFiles -> Action (IdeResult ModGuts) +generateCore runSimplifier input = do + packageState <- hscEnv <$> use_ GhcSessionDeps input + tm <- use_ TypeCheck input liftIO $ compileModule runSimplifier packageState (tmrModSummary tm) (tmrTypechecked tm) generateCoreRule :: Recorder (WithPriority Log) -> Rules () @@ -899,15 +929,15 @@ generateCoreRule recorder = define (cmapWithPrio LogShake recorder) $ \GenerateCore -> generateCore (RunSimplifier True) getModIfaceRule :: Recorder (WithPriority Log) -> Rules () -getModIfaceRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModIface f -> do - fileOfInterest <- use_ IsFileOfInterest f +getModIfaceRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModIface input -> do + fileOfInterest <- use_ IsFileOfInterest $ generalizeProjectInput input res <- case fileOfInterest of IsFOI status -> do -- Never load from disk for files of interest - tmr <- use_ TypeCheck f - linkableType <- getLinkableType f - hsc <- hscEnv <$> use_ GhcSessionDeps f - let compile = fmap ([],) $ use GenerateCore f + tmr <- use_ TypeCheck input + linkableType <- getLinkableType input + hsc <- hscEnv <$> use_ GhcSessionDeps input + let compile = fmap ([],) $ use GenerateCore input se <- getShakeExtras (diags, !mbHiFile) <- writeCoreFileIfNeeded se hsc linkableType compile tmr let fp = hiFileFingerPrint <$> mbHiFile @@ -918,7 +948,7 @@ getModIfaceRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ _ -> pure [] return (fp, (diags++hiDiags, mbHiFile)) NotFOI -> do - hiFile <- use GetModIfaceFromDiskAndIndex f + hiFile <- use GetModIfaceFromDiskAndIndex input let fp = hiFileFingerPrint <$> hiFile return (fp, ([], hiFile)) @@ -1089,21 +1119,21 @@ getLinkableRule recorder = return (fileHash <$ hmi, (warns, LinkableResult <$> hmi <*> pure fileHash)) -- | For now we always use bytecode unless something uses unboxed sums and tuples along with TH -getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType) +getLinkableType :: InputPath ProjectHaskellFiles -> Action (Maybe LinkableType) getLinkableType f = use_ NeedsCompilation f -needsCompilationRule :: NormalizedFilePath -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType)) -needsCompilationRule file - | "boot" `isSuffixOf` fromNormalizedFilePath file = +needsCompilationRule :: InputPath ProjectHaskellFiles -> Action (IdeResultNoDiagnosticsEarlyCutoff (Maybe LinkableType)) +needsCompilationRule input + | "boot" `isSuffixOf` fromNormalizedFilePath (unInputPath input) = pure (Just $ encodeLinkableType Nothing, Just Nothing) -needsCompilationRule file = do +needsCompilationRule input = do graph <- useNoFile GetModuleGraph res <- case graph of -- Treat as False if some reverse dependency header fails to parse Nothing -> pure Nothing - Just depinfo -> case immediateReverseDependencies file depinfo of + Just depinfo -> case immediateReverseDependencies input depinfo of -- If we fail to get immediate reverse dependencies, fail with an error message - Nothing -> fail $ "Failed to get the immediate reverse dependencies of " ++ show file + Nothing -> fail $ "Failed to get the immediate reverse dependencies of " ++ show (unInputPath input) Just revdeps -> do -- It's important to use stale data here to avoid wasted work. -- if NeedsCompilation fails for a module M its result will be under-approximated @@ -1199,8 +1229,8 @@ mainRule recorder RulesConfig{..} = do -- * Object/BCO -> NoLinkable : the prev linkable can be ignored, signal "no change" -- * otherwise : the prev linkable cannot be reused, signal "value has changed" if enableTemplateHaskell - then defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleWithCustomNewnessCheck (<=) $ \NeedsCompilation file -> - needsCompilationRule file + then defineEarlyCutoff (cmapWithPrio LogShake recorder) $ RuleWithCustomNewnessCheck (<=) $ \NeedsCompilation input -> + needsCompilationRule input else defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \NeedsCompilation _ -> return $ Just Nothing generateCoreRule recorder getImportMapRule recorder @@ -1210,13 +1240,13 @@ mainRule recorder RulesConfig{..} = do getLinkableRule recorder -- | Get HieFile for haskell file on NormalizedFilePath -getHieFile :: NormalizedFilePath -> Action (Maybe HieFile) -getHieFile nfp = runMaybeT $ do - HAR {hieAst} <- MaybeT $ use GetHieAst nfp - tmr <- MaybeT $ use TypeCheck nfp - ghc <- MaybeT $ use GhcSession nfp - msr <- MaybeT $ use GetModSummaryWithoutTimestamps nfp - source <- lift $ getSourceFileSource nfp +getHieFile :: InputPath ProjectHaskellFiles -> Action (Maybe HieFile) +getHieFile input = runMaybeT $ do + HAR {hieAst} <- MaybeT $ use GetHieAst $ generalizeProjectInput input + tmr <- MaybeT $ use TypeCheck input + ghc <- MaybeT $ use GhcSession input + msr <- MaybeT $ use GetModSummaryWithoutTimestamps input + source <- lift $ getSourceFileSource $ unInputPath input let exports = tcg_exports $ tmrTypechecked tmr typedAst <- MaybeT $ pure $ cast hieAst liftIO $ runHsc (hscEnv ghc) $ mkHieFile' (msrModSummary msr) exports typedAst source diff --git a/ghcide/src/Development/IDE/Core/Shake.hs b/ghcide/src/Development/IDE/Core/Shake.hs index e37c3741c7..eaf3bd365b 100644 --- a/ghcide/src/Development/IDE/Core/Shake.hs +++ b/ghcide/src/Development/IDE/Core/Shake.hs @@ -1,6 +1,7 @@ -- Copyright (c) 2019 The DAML Authors. All rights reserved. -- SPDX-License-Identifier: Apache-2.0 +{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DuplicateRecordFields #-} @@ -121,6 +122,7 @@ import Data.Vector (Vector) import qualified Data.Vector as Vector import Development.IDE.Core.Debouncer import Development.IDE.Core.FileUtils (getModTime) +import Development.IDE.Core.InputPath import Development.IDE.Core.PositionMapping import Development.IDE.Core.ProgressReporting import Development.IDE.Core.RuleTypes @@ -144,6 +146,7 @@ import Development.IDE.Graph.Database (ShakeDatabase, shakeNewDatabase, shakeProfileDatabase, shakeRunDatabaseForKeys) +import Development.IDE.Graph.Internal.Rules (InputClass(..)) import Development.IDE.Graph.Rule import Development.IDE.Types.Action import Development.IDE.Types.Diagnostics @@ -179,7 +182,8 @@ import System.FilePath hiding (makeRelative) import System.IO.Unsafe (unsafePerformIO) import System.Time.Extra import UnliftIO (MonadUnliftIO (withRunInIO)) - +import Development.IDE.Core.InputPath (InputPath(..)) +import Development.IDE.Types.Location (emptyFilePath) data Log = LogCreateHieDbExportsMapStart @@ -384,7 +388,7 @@ getPluginConfigAction plId = do -- This is called when we don't already have a result, or computing the rule failed. -- The result of this function will always be marked as 'stale', and a 'proper' rebuild of the rule will -- be queued if the rule hasn't run before. -addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,Maybe Int32))) -> Rules () +addPersistentRule :: IdeRule k i v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,Maybe Int32))) -> Rules () addPersistentRule k getVal = do ShakeExtras{persistentKeys} <- getShakeExtrasRules void $ liftIO $ atomically $ modifyTVar' persistentKeys $ insertKeyMap (newKey k) (fmap (fmap (first3 toDyn)) . getVal) @@ -452,10 +456,11 @@ getIdeOptionsIO ide = do -- | Return the most recent, potentially stale, value and a PositionMapping -- for the version of that value. -lastValueIO :: IdeRule k v => ShakeExtras -> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping)) -lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do +lastValueIO :: IdeRule k i v => ShakeExtras -> k -> InputPath i -> IO (Maybe (v, PositionMapping)) +lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k input = do - let readPersistent + let rawFile = unInputPath input + readPersistent | IdeTesting testing <- ideTesting s -- Don't read stale persistent values in tests , testing = pure Nothing | otherwise = do @@ -463,20 +468,20 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do mv <- runMaybeT $ do liftIO $ logWith (shakeRecorder s) Debug $ LogLookupPersistentKey (T.pack $ show k) f <- MaybeT $ pure $ lookupKeyMap (newKey k) pmap - (dv,del,ver) <- MaybeT $ runIdeAction "lastValueIO" s $ f file + (dv,del,ver) <- MaybeT $ runIdeAction "lastValueIO" s $ f rawFile MaybeT $ pure $ (,del,ver) <$> fromDynamic dv case mv of Nothing -> atomicallyNamed "lastValueIO 1" $ do - STM.focus (Focus.alter (alterValue $ Failed True)) (toKey k file) state + STM.focus (Focus.alter (alterValue $ Failed True)) (toKey k rawFile) state return Nothing Just (v,del,mbVer) -> do actual_version <- case mbVer of Just ver -> pure (Just $ VFSVersion ver) - Nothing -> (Just . ModificationTime <$> getModTime (fromNormalizedFilePath file)) + Nothing -> (Just . ModificationTime <$> getModTime (fromNormalizedFilePath rawFile)) `catch` (\(_ :: IOException) -> pure Nothing) atomicallyNamed "lastValueIO 2" $ do - STM.focus (Focus.alter (alterValue $ Stale (Just del) actual_version (toDyn v))) (toKey k file) state - Just . (v,) . addOldDelta del <$> mappingForVersion positionMapping file actual_version + STM.focus (Focus.alter (alterValue $ Stale (Just del) actual_version (toDyn v))) (toKey k rawFile) state + Just . (v,) . addOldDelta del <$> mappingForVersion positionMapping rawFile actual_version -- We got a new stale value from the persistent rule, insert it in the map without affecting diagnostics alterValue new Nothing = Just (ValueWithDiagnostics new mempty) -- If it wasn't in the map, give it empty diagnostics @@ -486,19 +491,19 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do -- Something already succeeded before, leave it alone _ -> old - atomicallyNamed "lastValueIO 4" (STM.lookup (toKey k file) state) >>= \case + atomicallyNamed "lastValueIO 4" (STM.lookup (toKey k rawFile) state) >>= \case Nothing -> readPersistent Just (ValueWithDiagnostics value _) -> case value of Succeeded ver (fromDynamic -> Just v) -> - atomicallyNamed "lastValueIO 5" $ Just . (v,) <$> mappingForVersion positionMapping file ver + atomicallyNamed "lastValueIO 5" $ Just . (v,) <$> mappingForVersion positionMapping rawFile ver Stale del ver (fromDynamic -> Just v) -> - atomicallyNamed "lastValueIO 6" $ Just . (v,) . maybe id addOldDelta del <$> mappingForVersion positionMapping file ver + atomicallyNamed "lastValueIO 6" $ Just . (v,) . maybe id addOldDelta del <$> mappingForVersion positionMapping rawFile ver Failed p | not p -> readPersistent _ -> pure Nothing -- | Return the most recent, potentially stale, value and a PositionMapping -- for the version of that value. -lastValue :: IdeRule k v => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) +lastValue :: IdeRule k i v => k -> InputPath i -> Action (Maybe (v, PositionMapping)) lastValue key file = do s <- getShakeExtras liftIO $ lastValueIO s key file @@ -513,8 +518,9 @@ mappingForVersion allMappings file (Just (VFSVersion ver)) = do return $ maybe zeroMapping snd $ EM.lookup ver =<< mapping mappingForVersion _ _ _ = pure zeroMapping -type IdeRule k v = - ( Shake.RuleResult k ~ v +type IdeRule k i v = + ( Shake.RuleInput k ~ i + , Shake.RuleResult k ~ v , Shake.ShakeValue k , Show v , Typeable v @@ -581,15 +587,15 @@ shakeDatabaseProfileIO mbProfileDir = do shakeProfileDatabase shakeDb $ dir file return (dir file) -setValues :: IdeRule k v +setValues :: IdeRule k i v => Values -> k - -> NormalizedFilePath + -> InputPath i -> Value v -> Vector FileDiagnostic -> STM () -setValues state key file val diags = - STM.insert (ValueWithDiagnostics (fmap toDyn val) diags) (toKey key file) state +setValues state key input val diags = + STM.insert (ValueWithDiagnostics (fmap toDyn val) diags) (toKey key $ unInputPath input) state -- | Delete the value stored for a given ide build key @@ -607,14 +613,14 @@ deleteValue ShakeExtras{state} key file = do -- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value. getValues :: - forall k v. - IdeRule k v => + forall k i v. + IdeRule k i v => Values -> k -> - NormalizedFilePath -> + InputPath i -> STM (Maybe (Value v, Vector FileDiagnostic)) -getValues state key file = do - STM.lookup (toKey key file) state >>= \case +getValues state key input = do + STM.lookup (toKey key $ unInputPath input) state >>= \case Nothing -> pure Nothing Just (ValueWithDiagnostics v diagsV) -> do let !r = seqValue $ fmap (fromJust . fromDynamic @v) v @@ -1010,23 +1016,23 @@ preservedKeys checkParents = HSet.fromList $ -- | Define a new Rule without early cutoff define - :: IdeRule k v - => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (IdeResult v)) -> Rules () + :: IdeRule k i v + => Recorder (WithPriority Log) -> (k -> InputPath i -> Action (IdeResult v)) -> Rules () define recorder op = defineEarlyCutoff recorder $ Rule $ \k v -> (Nothing,) <$> op k v defineNoDiagnostics - :: IdeRule k v - => Recorder (WithPriority Log) -> (k -> NormalizedFilePath -> Action (Maybe v)) -> Rules () + :: IdeRule k i v + => Recorder (WithPriority Log) -> (k -> InputPath i -> Action (Maybe v)) -> Rules () defineNoDiagnostics recorder op = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k v -> (Nothing,) <$> op k v -- | Request a Rule result if available -use :: IdeRule k v - => k -> NormalizedFilePath -> Action (Maybe v) -use key file = runIdentity <$> uses key (Identity file) +use :: IdeRule k i v + => k -> InputPath i -> Action (Maybe v) +use key input = runIdentity <$> uses key (Identity input) -- | Request a Rule result, it not available return the last computed result, if any, which may be stale -useWithStale :: IdeRule k v - => k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping)) +useWithStale :: IdeRule k i v + => k -> InputPath i -> Action (Maybe (v, PositionMapping)) useWithStale key file = runIdentity <$> usesWithStale key (Identity file) -- |Request a Rule result, it not available return the last computed result @@ -1036,9 +1042,9 @@ useWithStale key file = runIdentity <$> usesWithStale key (Identity file) -- none available. -- -- WARNING: Not suitable for PluginHandlers. Use `useWithStaleE` instead. -useWithStale_ :: IdeRule k v - => k -> NormalizedFilePath -> Action (v, PositionMapping) -useWithStale_ key file = runIdentity <$> usesWithStale_ key (Identity file) +useWithStale_ :: IdeRule k i v + => k -> InputPath i -> Action (v, PositionMapping) +useWithStale_ key input = runIdentity <$> usesWithStale_ key (Identity input) -- |Plural version of 'useWithStale_' -- @@ -1046,9 +1052,9 @@ useWithStale_ key file = runIdentity <$> usesWithStale_ key (Identity file) -- none available. -- -- WARNING: Not suitable for PluginHandlers. -usesWithStale_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f (v, PositionMapping)) -usesWithStale_ key files = do - res <- usesWithStale key files +usesWithStale_ :: (Traversable f, IdeRule k i v) => k -> f (InputPath i) -> Action (f (v, PositionMapping)) +usesWithStale_ key inputs = do + res <- usesWithStale key inputs case sequence res of Nothing -> liftIO $ throwIO $ BadDependency (show key) Just v -> return v @@ -1077,27 +1083,27 @@ data FastResult a = FastResult { stale :: Maybe (a,PositionMapping), uptoDate :: -- | Lookup value in the database and return with the stale value immediately -- Will queue an action to refresh the value. -- Might block the first time the rule runs, but never blocks after that. -useWithStaleFast :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (Maybe (v, PositionMapping)) -useWithStaleFast key file = stale <$> useWithStaleFast' key file +useWithStaleFast :: IdeRule k i v => k -> InputPath i -> IdeAction (Maybe (v, PositionMapping)) +useWithStaleFast key input = stale <$> useWithStaleFast' key input -- | Same as useWithStaleFast but lets you wait for an up to date result -useWithStaleFast' :: IdeRule k v => k -> NormalizedFilePath -> IdeAction (FastResult v) -useWithStaleFast' key file = do +useWithStaleFast' :: IdeRule k i v => k -> InputPath i -> IdeAction (FastResult v) +useWithStaleFast' key input = do -- This lookup directly looks up the key in the shake database and -- returns the last value that was computed for this key without -- checking freshness. -- Async trigger the key to be built anyway because we want to -- keep updating the value in the key. - waitValue <- delayedAction $ mkDelayedAction ("C:" ++ show key ++ ":" ++ fromNormalizedFilePath file) Debug $ use key file + waitValue <- delayedAction $ mkDelayedAction ("C:" ++ show key ++ ":" ++ fromNormalizedFilePath (unInputPath input)) Debug $ use key input s@ShakeExtras{state} <- askShake - r <- liftIO $ atomicallyNamed "useStateFast" $ getValues state key file + r <- liftIO $ atomicallyNamed "useStateFast" $ getValues state key input liftIO $ case r of -- block for the result if we haven't computed before Nothing -> do -- Check if we can get a stale value from disk - res <- lastValueIO s key file + res <- lastValueIO s key input case res of Nothing -> do a <- waitValue @@ -1105,11 +1111,11 @@ useWithStaleFast' key file = do Just _ -> pure $ FastResult res waitValue -- Otherwise, use the computed value even if it's out of date. Just _ -> do - res <- lastValueIO s key file + res <- lastValueIO s key input pure $ FastResult res waitValue -useNoFile :: IdeRule k v => k -> Action (Maybe v) -useNoFile key = use key emptyFilePath +useNoFile :: forall k v. IdeRule k NoFile v => k -> Action (Maybe v) +useNoFile key = use key (InputPath emptyFilePath) -- Requests a rule if available. -- @@ -1117,11 +1123,11 @@ useNoFile key = use key emptyFilePath -- none available. -- -- WARNING: Not suitable for PluginHandlers. Use `useE` instead. -use_ :: IdeRule k v => k -> NormalizedFilePath -> Action v -use_ key file = runIdentity <$> uses_ key (Identity file) +use_ :: IdeRule k i v => k -> InputPath i -> Action v +use_ key input = runIdentity <$> uses_ key (Identity input) -useNoFile_ :: IdeRule k v => k -> Action v -useNoFile_ key = use_ key emptyFilePath +useNoFile_ :: forall k v. IdeRule k NoFile v => k -> Action v +useNoFile_ key = use_ key (InputPath emptyFilePath) -- |Plural version of `use_` -- @@ -1129,7 +1135,7 @@ useNoFile_ key = use_ key emptyFilePath -- none available. -- -- WARNING: Not suitable for PluginHandlers. Use `usesE` instead. -uses_ :: (Traversable f, IdeRule k v) => k -> f NormalizedFilePath -> Action (f v) +uses_ :: (Traversable f, IdeRule k i v) => k -> f (InputPath i) -> Action (f v) uses_ key files = do res <- uses key files case sequence res of @@ -1137,100 +1143,106 @@ uses_ key files = do Just v -> return v -- | Plural version of 'use' -uses :: (Traversable f, IdeRule k v) - => k -> f NormalizedFilePath -> Action (f (Maybe v)) -uses key files = fmap (\(A value) -> currentValue value) <$> apply (fmap (Q . (key,)) files) +uses :: (Traversable f, IdeRule k i v) + => k -> f (InputPath i) -> Action (f (Maybe v)) +uses key files = fmap (\(A value) -> currentValue value) <$> apply (fmap (Q . (key,) . unInputPath) files) -- | Return the last computed result which might be stale. -usesWithStale :: (Traversable f, IdeRule k v) - => k -> f NormalizedFilePath -> Action (f (Maybe (v, PositionMapping))) -usesWithStale key files = do - _ <- apply (fmap (Q . (key,)) files) +usesWithStale :: (Traversable f, IdeRule k i v) + => k -> f (InputPath i) -> Action (f (Maybe (v, PositionMapping))) +usesWithStale key inputs = do + _ <- apply (fmap (Q . (key,) . unInputPath) inputs) -- We don't look at the result of the 'apply' since 'lastValue' will -- return the most recent successfully computed value regardless of -- whether the rule succeeded or not. - traverse (lastValue key) files + traverse (lastValue key) inputs -useWithoutDependency :: IdeRule k v - => k -> NormalizedFilePath -> Action (Maybe v) -useWithoutDependency key file = - (\(Identity (A value)) -> currentValue value) <$> applyWithoutDependency (Identity (Q (key, file))) +useWithoutDependency :: IdeRule k i v + => k -> InputPath i -> Action (Maybe v) +useWithoutDependency key input = + (\(Identity (A value)) -> currentValue value) <$> applyWithoutDependency (Identity (Q (key, unInputPath input))) -data RuleBody k v - = Rule (k -> NormalizedFilePath -> Action (Maybe BS.ByteString, IdeResult v)) - | RuleNoDiagnostics (k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v)) +data RuleBody k i v + = Rule (k -> InputPath i -> Action (Maybe BS.ByteString, IdeResult v)) + | RuleNoDiagnostics (k -> InputPath i -> Action (Maybe BS.ByteString, Maybe v)) | RuleWithCustomNewnessCheck { newnessCheck :: BS.ByteString -> BS.ByteString -> Bool - , build :: k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v) + , build :: k -> InputPath i -> Action (Maybe BS.ByteString, Maybe v) } - | RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe BS.ByteString, IdeResult v)) + | RuleWithOldValue (k -> InputPath i -> Value v -> Action (Maybe BS.ByteString, IdeResult v)) -- | Define a new Rule with early cutoff defineEarlyCutoff - :: IdeRule k v + :: forall k i v + . IdeRule k i v => Recorder (WithPriority Log) - -> RuleBody k v + -> RuleBody k i v -> Rules () -defineEarlyCutoff recorder (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do +defineEarlyCutoff recorder (Rule op) = addRule $ \(Q (key, rawFile)) (old :: Maybe BS.ByteString) mode -> otTracedAction key rawFile mode traceA $ \traceDiagnostics -> do extras <- getShakeExtras let diagnostics ver diags = do traceDiagnostics diags - updateFileDiagnostics recorder file ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags - defineEarlyCutoff' diagnostics (==) key file old mode $ const $ op key file -defineEarlyCutoff recorder (RuleNoDiagnostics op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do + updateFileDiagnostics recorder rawFile ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags + input = InputPath @i rawFile + defineEarlyCutoff' diagnostics (==) key input old mode $ const $ op key input +defineEarlyCutoff recorder (RuleNoDiagnostics op) = addRule $ \(Q (key, rawFile)) (old :: Maybe BS.ByteString) mode -> otTracedAction key rawFile mode traceA $ \traceDiagnostics -> do let diagnostics _ver diags = do traceDiagnostics diags mapM_ (logWith recorder Warning . LogDefineEarlyCutoffRuleNoDiagHasDiag) diags - defineEarlyCutoff' diagnostics (==) key file old mode $ const $ second (mempty,) <$> op key file + input = InputPath @i rawFile + defineEarlyCutoff' diagnostics (==) key input old mode $ const $ second (mempty,) <$> op key input defineEarlyCutoff recorder RuleWithCustomNewnessCheck{..} = - addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> - otTracedAction key file mode traceA $ \ traceDiagnostics -> do + addRule $ \(Q (key, rawFile)) (old :: Maybe BS.ByteString) mode -> + otTracedAction key rawFile mode traceA $ \ traceDiagnostics -> do let diagnostics _ver diags = do traceDiagnostics diags mapM_ (logWith recorder Warning . LogDefineEarlyCutoffRuleCustomNewnessHasDiag) diags - defineEarlyCutoff' diagnostics newnessCheck key file old mode $ - const $ second (mempty,) <$> build key file -defineEarlyCutoff recorder (RuleWithOldValue op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do + input = InputPath @i rawFile + defineEarlyCutoff' diagnostics newnessCheck key input old mode $ + const $ second (mempty,) <$> build key input +defineEarlyCutoff recorder (RuleWithOldValue op) = addRule $ \(Q (key, rawFile)) (old :: Maybe BS.ByteString) mode -> otTracedAction key rawFile mode traceA $ \traceDiagnostics -> do extras <- getShakeExtras let diagnostics ver diags = do traceDiagnostics diags - updateFileDiagnostics recorder file ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags - defineEarlyCutoff' diagnostics (==) key file old mode $ op key file + updateFileDiagnostics recorder rawFile ver (newKey key) extras . map (\(_,y,z) -> (y,z)) $ diags + input = InputPath @i rawFile + defineEarlyCutoff' diagnostics (==) key input old mode $ op key input -defineNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () -defineNoFile recorder f = defineNoDiagnostics recorder $ \k file -> do - if file == emptyFilePath then do res <- f k; return (Just res) else - fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file" +defineNoFile :: forall k v. IdeRule k NoFile v => Recorder (WithPriority Log) -> (k -> Action v) -> Rules () +defineNoFile recorder f = defineNoDiagnostics recorder $ \k _ -> do + res <- f k + return (Just res) -defineEarlyCutOffNoFile :: IdeRule k v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules () -defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k file -> do - if file == emptyFilePath then do (hashString, res) <- f k; return (Just hashString, Just res) else - fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file" +defineEarlyCutOffNoFile :: forall k v. IdeRule k NoFile v => Recorder (WithPriority Log) -> (k -> Action (BS.ByteString, v)) -> Rules () +defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnostics $ \k _ -> do + (hashString, res) <- f k + return (Just hashString, Just res) defineEarlyCutoff' - :: forall k v. IdeRule k v + :: forall k i v. IdeRule k i v => (Maybe Int32 -> [FileDiagnostic] -> Action ()) -- ^ update diagnostics -- | compare current and previous for freshness -> (BS.ByteString -> BS.ByteString -> Bool) -> k - -> NormalizedFilePath + -> InputPath i -> Maybe BS.ByteString -> RunMode -> (Value v -> Action (Maybe BS.ByteString, IdeResult v)) -> Action (RunResult (A (RuleResult k))) -defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do +defineEarlyCutoff' doDiagnostics cmp key input mbOld mode action = do + let rawFile = unInputPath input ShakeExtras{state, progress, dirtyKeys} <- getShakeExtras options <- getIdeOptions let trans g x = withRunInIO $ \run -> g (run x) - (if optSkipProgress options key then id else trans (inProgress progress file)) $ do + (if optSkipProgress options key then id else trans (inProgress progress rawFile)) $ do val <- case mbOld of Just old | mode == RunDependenciesSame -> do - mbValue <- liftIO $ atomicallyNamed "define - read 1" $ getValues state key file + mbValue <- liftIO $ atomicallyNamed "define - read 1" $ getValues state key input case mbValue of -- No changes in the dependencies and we have -- an existing successful result. Just (v@(Succeeded _ x), diags) -> do - ver <- estimateFileVersionUnsafely key (Just x) file + ver <- estimateFileVersionUnsafely key (Just x) input doDiagnostics (vfsVersion =<< ver) $ Vector.toList diags return $ Just $ RunResult ChangedNothing old (A v) $ return () _ -> return Nothing @@ -1241,7 +1253,7 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do res <- case val of Just res -> return res Nothing -> do - staleV <- liftIO $ atomicallyNamed "define -read 3" $ getValues state key file <&> \case + staleV <- liftIO $ atomicallyNamed "define -read 3" $ getValues state key input <&> \case Nothing -> Failed False Just (Succeeded ver v, _) -> Stale Nothing ver v Just (Stale d ver v, _) -> Stale d ver v @@ -1249,9 +1261,9 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do (mbBs, (diags, mbRes)) <- actionCatch (do v <- action staleV; liftIO $ evaluate $ force v) $ \(e :: SomeException) -> do - pure (Nothing, ([ideErrorText file $ T.pack $ show e | not $ isBadDependency e],Nothing)) + pure (Nothing, ([ideErrorText rawFile $ T.pack $ show e | not $ isBadDependency e],Nothing)) - ver <- estimateFileVersionUnsafely key mbRes file + ver <- estimateFileVersionUnsafely key mbRes input (bs, res) <- case mbRes of Nothing -> do pure (toShakeValue ShakeStale mbBs, staleV) @@ -1269,8 +1281,8 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do (A res) $ do -- this hook needs to be run in the same transaction as the key is marked clean -- see Note [Housekeeping rule cache and dirty key outside of hls-graph] - setValues state key file res (Vector.fromList diags) - modifyTVar' dirtyKeys (deleteKeySet $ toKey key file) + setValues state key input res (Vector.fromList diags) + modifyTVar' dirtyKeys (deleteKeySet $ toKey key rawFile) return res where -- Highly unsafe helper to compute the version of a file @@ -1279,10 +1291,10 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do estimateFileVersionUnsafely :: k -> Maybe v - -> NormalizedFilePath + -> InputPath i -> Action (Maybe FileVersion) - estimateFileVersionUnsafely _k v fp - | fp == emptyFilePath = pure Nothing + estimateFileVersionUnsafely _k v input + | unInputPath input == emptyFilePath = pure Nothing | Just Refl <- eqT @k @GetModificationTime = pure v -- GetModificationTime depends on these rules, so avoid creating a cycle | Just Refl <- eqT @k @AddWatchedFile = pure Nothing @@ -1292,7 +1304,7 @@ defineEarlyCutoff' doDiagnostics cmp key file mbOld mode action = do -- For all other rules - compute the version properly without: -- * creating a dependency: If everything depends on GetModificationTime, we lose early cutoff -- * creating bogus "file does not exists" diagnostics - | otherwise = useWithoutDependency (GetModificationTime_ False) fp + | otherwise = useWithoutDependency (GetModificationTime_ False) (InputPath $ unInputPath input) -- Note [Housekeeping rule cache and dirty key outside of hls-graph] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1457,9 +1469,10 @@ kickSignal testing lspEnv files msg = when testing $ liftIO $ mRunLspT lspEnv $ toJSON $ map fromNormalizedFilePath files -- | Add kick start/done signal to rule -runWithSignal :: (KnownSymbol s0, KnownSymbol s1, IdeRule k v) => Proxy s0 -> Proxy s1 -> [NormalizedFilePath] -> k -> Action () -runWithSignal msgStart msgEnd files rule = do +runWithSignal :: (KnownSymbol s0, KnownSymbol s1, IdeRule k i v) => Proxy s0 -> Proxy s1 -> [InputPath i] -> k -> Action () +runWithSignal msgStart msgEnd inputs rule = do + let files = map unInputPath inputs ShakeExtras{ideTesting = Options.IdeTesting testing, lspEnv} <- getShakeExtras kickSignal testing lspEnv files msgStart - void $ uses rule files + void $ uses rule inputs kickSignal testing lspEnv files msgEnd diff --git a/ghcide/src/Development/IDE/Import/DependencyInformation.hs b/ghcide/src/Development/IDE/Import/DependencyInformation.hs index 5372a1364a..697dcb9e0c 100644 --- a/ghcide/src/Development/IDE/Import/DependencyInformation.hs +++ b/ghcide/src/Development/IDE/Import/DependencyInformation.hs @@ -49,11 +49,13 @@ import Data.Maybe import Data.Tuple.Extra hiding (first, second) import Development.IDE.GHC.Compat import Development.IDE.GHC.Orphans () +import Development.IDE.Graph.Internal.Rules import Development.IDE.Import.FindImports (ArtifactsLocation (..)) import Development.IDE.Types.Diagnostics import Development.IDE.Types.Location import GHC.Generics (Generic) import Prelude hiding (mod) +import Development.IDE.Core.InputPath (InputPath(..)) -- | The imports for a given module. @@ -335,10 +337,10 @@ transitiveReverseDependencies file DependencyInformation{..} = do in IntSet.foldr go res new -- | Immediate reverse dependencies of a file -immediateReverseDependencies :: NormalizedFilePath -> DependencyInformation -> Maybe [NormalizedFilePath] -immediateReverseDependencies file DependencyInformation{..} = do - FilePathId cur_id <- lookupPathToId depPathIdMap file - return $ map (idToPath depPathIdMap . FilePathId) (maybe mempty IntSet.toList (IntMap.lookup cur_id depReverseModuleDeps)) +immediateReverseDependencies :: InputPath ProjectHaskellFiles -> DependencyInformation -> Maybe [InputPath ProjectHaskellFiles] +immediateReverseDependencies input DependencyInformation{..} = do + FilePathId cur_id <- lookupPathToId depPathIdMap $ unInputPath input + return $ map (InputPath . idToPath depPathIdMap . FilePathId) (maybe mempty IntSet.toList (IntMap.lookup cur_id depReverseModuleDeps)) -- | returns all transitive dependencies in topological order. transitiveDeps :: DependencyInformation -> NormalizedFilePath -> Maybe TransitiveDependencies diff --git a/ghcide/src/Development/IDE/LSP/Outline.hs b/ghcide/src/Development/IDE/LSP/Outline.hs index af2a0f1c97..2051e3a06e 100644 --- a/ghcide/src/Development/IDE/LSP/Outline.hs +++ b/ghcide/src/Development/IDE/LSP/Outline.hs @@ -29,6 +29,7 @@ import Language.LSP.Protocol.Types (DocumentSymbol (..), TextDocumentIdentifier (TextDocumentIdentifier), type (|?) (InL, InR), uriToFilePath) +import Development.IDE.Core.InputPath (InputPath(InputPath)) moduleOutline @@ -36,7 +37,7 @@ moduleOutline moduleOutline ideState _ DocumentSymbolParams{ _textDocument = TextDocumentIdentifier uri } = liftIO $ case uriToFilePath uri of Just (toNormalizedFilePath' -> fp) -> do - mb_decls <- fmap fst <$> runAction "Outline" ideState (useWithStale GetParsedModule fp) + mb_decls <- fmap fst <$> runAction "Outline" ideState (useWithStale GetParsedModule $ InputPath fp) pure $ case mb_decls of Nothing -> InL [] Just ParsedModule { pm_parsed_source = L _ltop HsModule { hsmodName, hsmodDecls, hsmodImports } } diff --git a/ghcide/src/Development/IDE/Plugin/Completions/Types.hs b/ghcide/src/Development/IDE/Plugin/Completions/Types.hs index 2d950d66a9..fda1c48d2b 100644 --- a/ghcide/src/Development/IDE/Plugin/Completions/Types.hs +++ b/ghcide/src/Development/IDE/Plugin/Completions/Types.hs @@ -19,6 +19,7 @@ import Data.Text (Text) import Data.Typeable (Typeable) import Development.IDE.GHC.Compat import Development.IDE.Graph (RuleResult) +import Development.IDE.Graph.Internal.Rules (RuleInput, InputClass(..)) import Development.IDE.Spans.Common () import GHC.Generics (Generic) import qualified GHC.Types.Name.Occurrence as Occ @@ -28,7 +29,9 @@ import qualified Language.LSP.Protocol.Types as J -- | Produce completions info for a file type instance RuleResult LocalCompletions = CachedCompletions +type instance RuleInput LocalCompletions = ProjectHaskellFiles type instance RuleResult NonLocalCompletions = CachedCompletions +type instance RuleInput NonLocalCompletions = ProjectHaskellFiles data LocalCompletions = LocalCompletions deriving (Eq, Show, Typeable, Generic) diff --git a/ghcide/src/Development/IDE/Plugin/Test.hs b/ghcide/src/Development/IDE/Plugin/Test.hs index e24bcfeee9..3aa9becde4 100644 --- a/ghcide/src/Development/IDE/Plugin/Test.hs +++ b/ghcide/src/Development/IDE/Plugin/Test.hs @@ -52,6 +52,8 @@ import Language.LSP.Protocol.Types import qualified "list-t" ListT import qualified StmContainers.Map as STM import System.Time.Extra +import Development.IDE.Core.InputPath (InputPath(InputPath), generalizeProjectInput) +import Development.IDE.Graph.Internal.Rules (InputClass(ProjectHaskellFiles)) type Age = Int data TestRequest @@ -98,7 +100,7 @@ testRequestHandler _ (BlockSeconds secs) = do return (Right A.Null) testRequestHandler s (GetInterfaceFilesDir file) = liftIO $ do let nfp = fromUri $ toNormalizedUri file - sess <- runAction "Test - GhcSession" s $ use_ GhcSession nfp + sess <- runAction "Test - GhcSession" s $ use_ GhcSession $ InputPath nfp let hiPath = hiDir $ hsc_dflags $ hscEnv sess return $ Right (toJSON hiPath) testRequestHandler s GetShakeSessionQueueCount = liftIO $ do @@ -111,7 +113,7 @@ testRequestHandler s WaitForShakeQueue = liftIO $ do return $ Right A.Null testRequestHandler s (WaitForIdeRule k file) = liftIO $ do let nfp = fromUri $ toNormalizedUri file - success <- runAction ("WaitForIdeRule " <> k <> " " <> show file) s $ parseAction (fromString k) nfp + success <- runAction ("WaitForIdeRule " <> k <> " " <> show file) s $ parseAction (fromString k) $ InputPath $ nfp let res = WaitForIdeRuleResult <$> success return $ bimap PluginInvalidParams toJSON res testRequestHandler s GetBuildKeysBuilt = liftIO $ do @@ -147,7 +149,7 @@ getDatabaseKeys field db = do step <- shakeGetBuildStep db return [ k | (k, res) <- keys, field res == Step step] -parseAction :: CI String -> NormalizedFilePath -> Action (Either Text Bool) +parseAction :: CI String -> InputPath ProjectHaskellFiles -> Action (Either Text Bool) parseAction "typecheck" fp = Right . isJust <$> use TypeCheck fp parseAction "getLocatedImports" fp = Right . isJust <$> use GetLocatedImports fp parseAction "getmodsummary" fp = Right . isJust <$> use GetModSummary fp @@ -155,8 +157,8 @@ parseAction "getmodsummarywithouttimestamps" fp = Right . isJust <$> use GetModS parseAction "getparsedmodule" fp = Right . isJust <$> use GetParsedModule fp parseAction "ghcsession" fp = Right . isJust <$> use GhcSession fp parseAction "ghcsessiondeps" fp = Right . isJust <$> use GhcSessionDeps fp -parseAction "gethieast" fp = Right . isJust <$> use GetHieAst fp -parseAction "getFileContents" fp = Right . isJust <$> use GetFileContents fp +parseAction "gethieast" fp = Right . isJust <$> use GetHieAst (generalizeProjectInput fp) +parseAction "getFileContents" fp = Right . isJust <$> use GetFileContents (generalizeProjectInput fp) parseAction other _ = return $ Left $ "Cannot parse ide rule: " <> pack (original other) -- | a command that blocks forever. Used for testing diff --git a/ghcide/src/Development/IDE/Plugin/TypeLenses.hs b/ghcide/src/Development/IDE/Plugin/TypeLenses.hs index 51d25e995b..a94bbfa6b1 100644 --- a/ghcide/src/Development/IDE/Plugin/TypeLenses.hs +++ b/ghcide/src/Development/IDE/Plugin/TypeLenses.hs @@ -24,7 +24,7 @@ import Data.Aeson.Types (toJSON) import qualified Data.Aeson.Types as A import Data.List (find) import qualified Data.Map as Map -import Data.Maybe (catMaybes, maybeToList) +import Data.Maybe (catMaybes, maybeToList, listToMaybe) import qualified Data.Text as T import Development.IDE (GhcSession (..), HscEnvEq (hscEnv), @@ -81,6 +81,9 @@ import Language.LSP.Protocol.Types (ApplyWorkspaceEditParams WorkspaceEdit (WorkspaceEdit), type (|?) (..)) import Text.Regex.TDFA ((=~)) +import Development.IDE.Graph (RuleInput) +import Development.IDE.Graph.Internal.Rules (InputClass(ProjectHaskellFiles)) +import Development.IDE.Core.InputPath (classifyProjectHaskellInputs) data Log = LogShake Shake.Log deriving Show @@ -167,18 +170,24 @@ codeLensProvider ideState pId CodeLensParams{_textDocument = TextDocumentIdentif codeLensResolveProvider :: ResolveFunction IdeState TypeLensesResolve Method_CodeLensResolve codeLensResolveProvider ideState pId lens@CodeLens{_range} uri TypeLensesResolve = do nfp <- getNormalizedFilePathE uri - (gblSigs@(GlobalBindingTypeSigsResult _), pm) <- - runActionE "codeLens.GetGlobalBindingTypeSigs" ideState - $ useWithStaleE GetGlobalBindingTypeSigs nfp + let mInput = listToMaybe $ classifyProjectHaskellInputs [nfp] + (mGblSigs, mPm) <- + case mInput of + Nothing -> pure (Nothing, Nothing) + Just input -> do + (gblSigs@(GlobalBindingTypeSigsResult _), pm) <- + runActionE "codeLens.GetGlobalBindingTypeSigs" ideState + $ useWithStaleE GetGlobalBindingTypeSigs input + pure (Just gblSigs, Just pm) -- regardless of how the original lens was generated, we want to get the range -- that the global bindings rule would expect here, hence the need to reverse -- position map the range, regardless of whether it was position mapped in the -- beginning or freshly taken from diagnostics. - newRange <- handleMaybe PluginStaleResolve (fromCurrentRange pm _range) + newRange <- handleMaybe PluginStaleResolve (mPm >>= flip fromCurrentRange _range) -- We also pass on the PositionMapping so that the generated text edit can -- have the range adjusted. (title, edit) <- - handleMaybe PluginStaleResolve $ suggestGlobalSignature' False (Just gblSigs) (Just pm) newRange + handleMaybe PluginStaleResolve $ suggestGlobalSignature' False mGblSigs mPm newRange pure $ lens & L.command ?~ generateLensCommand pId uri title edit generateLensCommand :: PluginId -> Uri -> T.Text -> TextEdit -> Command @@ -295,13 +304,14 @@ instance NFData GlobalBindingTypeSigsResult where rnf = rwhnf type instance RuleResult GetGlobalBindingTypeSigs = GlobalBindingTypeSigsResult +type instance RuleInput GetGlobalBindingTypeSigs = ProjectHaskellFiles rules :: Recorder (WithPriority Log) -> Rules () rules recorder = do - define (cmapWithPrio LogShake recorder) $ \GetGlobalBindingTypeSigs nfp -> do - tmr <- use TypeCheck nfp + define (cmapWithPrio LogShake recorder) $ \GetGlobalBindingTypeSigs input -> do + tmr <- use TypeCheck input -- we need session here for tidying types - hsc <- use GhcSession nfp + hsc <- use GhcSession input result <- liftIO $ gblBindingType (hscEnv <$> hsc) (tmrTypechecked <$> tmr) pure ([], result) diff --git a/ghcide/src/Development/IDE/Spans/AtPoint.hs b/ghcide/src/Development/IDE/Spans/AtPoint.hs index 88c6570b23..07bc144f5f 100644 --- a/ghcide/src/Development/IDE/Spans/AtPoint.hs +++ b/ghcide/src/Development/IDE/Spans/AtPoint.hs @@ -208,11 +208,11 @@ gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos atPoint :: IdeOptions -> HieAstResult - -> DocAndTyThingMap - -> HscEnv + -> Maybe DocAndTyThingMap + -> Maybe HscEnv -> Position -> IO (Maybe (Maybe Range, [T.Text])) -atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env pos = +atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) mDkMap mEnv pos = listToMaybe <$> sequence (pointCommand hf pos hoverInfo) where -- Hover info for values/data @@ -251,9 +251,15 @@ atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env prettyName (Right n, dets) = pure $ T.unlines $ wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind)) : maybeToList (pretty (definedAt n) (prettyPackageName n)) - ++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n + ++ catMaybes [ T.unlines . spanDocToMarkdown <$> maybeDoc ] - where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n + where maybeKind = do + (DKMap _ km) <- mDkMap + nameEnv <- lookupNameEnv km n + printOutputable <$> safeTyThingType nameEnv + maybeDoc = do + (DKMap dm _) <- mDkMap + lookupNameEnv dm n pretty Nothing Nothing = Nothing pretty (Just define) Nothing = Just $ define <> "\n" pretty Nothing (Just pkgName) = Just $ pkgName <> "\n" @@ -270,7 +276,8 @@ atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env -- the package(with version) this `ModuleName` belongs to. packageNameForImportStatement :: ModuleName -> IO T.Text packageNameForImportStatement mod = do - mpkg <- findImportedModule env mod :: IO (Maybe Module) + mpkg <- fmap join $ sequence $ + flip findImportedModule mod <$> mEnv :: IO (Maybe Module) let moduleName = printOutputable mod case mpkg >>= packageNameWithVersion of Nothing -> pure moduleName @@ -278,14 +285,22 @@ atPoint IdeOptions{} (HAR _ hf _ _ (kind :: HieKind hietype)) (DKMap dm km) env -- Return the package name and version of a module. -- For example, given module `Data.List`, it should return something like `base-4.x`. - packageNameWithVersion :: Module -> Maybe T.Text - packageNameWithVersion m = do - let pid = moduleUnit m - conf <- lookupUnit env pid - let pkgName = T.pack $ unitPackageNameString conf - version = T.pack $ showVersion (unitPackageVersion conf) - pure $ pkgName <> "-" <> version - + packageNameWithVersion m = let pid = moduleUnit m in + case mEnv of + -- If we have an HscEnv (because this is a project file), + -- we can get the package name from that. + Just env -> do + conf <- lookupUnit env pid + let pkgName = T.pack $ unitPackageNameString conf + version = T.pack $ showVersion (unitPackageVersion conf) + pure $ pkgName <> "-" <> version + -- If we don't have an HscEnv (because this is a dependency file), + -- then we can get a similar format for the package name + -- from the UnitId. + Nothing -> + let uid = toUnitId pid + pkgStr = takeWhile (/= ':') $ show uid + in Just $ T.pack pkgStr -- Type info for the current node, it may contains several symbols -- for one range, like wildcard types :: [hietype] diff --git a/ghcide/src/Development/IDE/Spans/Pragmas.hs b/ghcide/src/Development/IDE/Spans/Pragmas.hs index a2b4981a38..52ff905109 100644 --- a/ghcide/src/Development/IDE/Spans/Pragmas.hs +++ b/ghcide/src/Development/IDE/Spans/Pragmas.hs @@ -15,7 +15,7 @@ import qualified Data.List as List import qualified Data.Maybe as Maybe import Data.Text (Text, pack) import qualified Data.Text as Text -import Development.IDE (srcSpanToRange, IdeState, NormalizedFilePath, GhcSession (..), getFileContents, hscEnv, runAction) +import Development.IDE (srcSpanToRange, IdeState, GhcSession (..), getFileContents, hscEnv, runAction) import Development.IDE.GHC.Compat import Development.IDE.GHC.Compat.Util import qualified Language.LSP.Protocol.Types as LSP @@ -26,6 +26,8 @@ import Ide.Types (PluginId(..)) import qualified Data.Text as T import Development.IDE.Core.PluginUtils import qualified Language.LSP.Protocol.Lens as L +import Development.IDE.Core.InputPath (InputPath, generalizeProjectInput) +import Development.IDE.Graph.Internal.Rules (InputClass(ProjectHaskellFiles)) getNextPragmaInfo :: DynFlags -> Maybe Text -> NextPragmaInfo getNextPragmaInfo dynFlags mbSourceText = @@ -53,10 +55,10 @@ insertNewPragma (NextPragmaInfo nextPragmaLine _) newPragma = LSP.TextEdit prag pragmaInsertPosition = LSP.Position (fromIntegral nextPragmaLine) 0 pragmaInsertRange = LSP.Range pragmaInsertPosition pragmaInsertPosition -getFirstPragma :: MonadIO m => PluginId -> IdeState -> NormalizedFilePath -> ExceptT PluginError m NextPragmaInfo -getFirstPragma (PluginId pId) state nfp = do - (hscEnv -> hsc_dflags -> sessionDynFlags, _) <- runActionE (T.unpack pId <> ".GhcSession") state $ useWithStaleE GhcSession nfp - (_, fileContents) <- liftIO $ runAction (T.unpack pId <> ".GetFileContents") state $ getFileContents nfp +getFirstPragma :: MonadIO m => PluginId -> IdeState -> InputPath ProjectHaskellFiles -> ExceptT PluginError m NextPragmaInfo +getFirstPragma (PluginId pId) state input = do + (hscEnv -> hsc_dflags -> sessionDynFlags, _) <- runActionE (T.unpack pId <> ".GhcSession") state $ useWithStaleE GhcSession input + (_, fileContents) <- liftIO $ runAction (T.unpack pId <> ".GetFileContents") state $ getFileContents $ generalizeProjectInput input pure $ getNextPragmaInfo sessionDynFlags fileContents -- Pre-declaration comments parser ----------------------------------------------------- diff --git a/hls-graph/src/Development/IDE/Graph.hs b/hls-graph/src/Development/IDE/Graph.hs index 81ad3b3dfd..45f473ec93 100644 --- a/hls-graph/src/Development/IDE/Graph.hs +++ b/hls-graph/src/Development/IDE/Graph.hs @@ -12,7 +12,7 @@ module Development.IDE.Graph( -- * Explicit parallelism parallel, -- * Oracle rules - ShakeValue, RuleResult, + ShakeValue, RuleResult, RuleInput, -- * Special rules alwaysRerun, -- * Actions for inspecting the keys in the database diff --git a/hls-graph/src/Development/IDE/Graph/Internal/Rules.hs b/hls-graph/src/Development/IDE/Graph/Internal/Rules.hs index 9a5f36ca35..561f11098c 100644 --- a/hls-graph/src/Development/IDE/Graph/Internal/Rules.hs +++ b/hls-graph/src/Development/IDE/Graph/Internal/Rules.hs @@ -23,6 +23,16 @@ import Development.IDE.Graph.Internal.Types -- | The type mapping between the @key@ or a rule and the resulting @value@. type family RuleResult key -- = value +-- | The broadest class of files a Rule is applicable to +data InputClass + = ProjectHaskellFiles + | AllHaskellFiles + | NoFile + +-- | The type mapping between the @key@ or a rule and the +-- class of files it is applicable to. +type family RuleInput key :: InputClass + action :: Action a -> Rules () action x = do ref <- Rules $ asks rulesActions