Skip to content

Commit 94573be

Browse files
pepeiborrajneiramergify[bot]
authored
Avoid redundant work in diagnostics pass (#1514)
* define rules without diagnostics * Export getFileContents rule definition * Reexport new definitions from top level * forgot the all importan boolean Co-authored-by: Javier Neira <atreyu.bbb@gmail.com> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 00c954d commit 94573be

File tree

6 files changed

+118
-65
lines changed

6 files changed

+118
-65
lines changed

ghcide/src/Development/IDE.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,8 @@ import Development.IDE.Core.IdeConfiguration as X (IdeConfiguration (.
1212
isWorkspaceFile)
1313
import Development.IDE.Core.OfInterest as X (getFilesOfInterest)
1414
import Development.IDE.Core.RuleTypes as X
15-
import Development.IDE.Core.Rules as X (getAtPoint,
15+
import Development.IDE.Core.Rules as X (IsHiFileStable (..),
16+
getAtPoint,
1617
getClientConfigAction,
1718
getDefinition,
1819
getParsedModule,
@@ -21,10 +22,12 @@ import Development.IDE.Core.Service as X (runAction)
2122
import Development.IDE.Core.Shake as X (FastResult (..),
2223
IdeAction (..),
2324
IdeRule, IdeState,
25+
RuleBody (..),
2426
ShakeExtras,
2527
actionLogger,
2628
define,
2729
defineEarlyCutoff,
30+
defineNoDiagnostics,
2831
getClientConfig,
2932
getPluginConfig,
3033
ideLogger,

ghcide/src/Development/IDE/Core/FileExists.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -200,7 +200,7 @@ fileExistsRules lspEnv vfs = do
200200
-- Requires an lsp client that provides WatchedFiles notifications, but assumes that this has already been checked.
201201
fileExistsRulesFast :: (NormalizedFilePath -> Action Bool) -> VFSHandle -> Rules ()
202202
fileExistsRulesFast isWatched vfs =
203-
defineEarlyCutoff $ \GetFileExists file -> do
203+
defineEarlyCutoff $ RuleNoDiagnostics $ \GetFileExists file -> do
204204
isWF <- isWatched file
205205
if isWF
206206
then fileExistsFast vfs file
@@ -222,7 +222,7 @@ For the VFS lookup, however, we won't get prompted to flush the result, so inste
222222
we use 'alwaysRerun'.
223223
-}
224224

225-
fileExistsFast :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
225+
fileExistsFast :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool)
226226
fileExistsFast vfs file = do
227227
-- Could in principle use 'alwaysRerun' here, but it's too slwo, See Note [Invalidating file existence results]
228228
mp <- getFileExistsMapUntracked
@@ -233,21 +233,21 @@ fileExistsFast vfs file = do
233233
-- We don't know about it: use the slow route.
234234
-- Note that we do *not* call 'fileExistsSlow', as that would trigger 'alwaysRerun'.
235235
Nothing -> liftIO $ getFileExistsVFS vfs file
236-
pure (summarizeExists exist, ([], Just exist))
236+
pure (summarizeExists exist, Just exist)
237237

238238
summarizeExists :: Bool -> Maybe BS.ByteString
239239
summarizeExists x = Just $ if x then BS.singleton 1 else BS.empty
240240

241241
fileExistsRulesSlow :: VFSHandle -> Rules ()
242242
fileExistsRulesSlow vfs =
243-
defineEarlyCutoff $ \GetFileExists file -> fileExistsSlow vfs file
243+
defineEarlyCutoff $ RuleNoDiagnostics $ \GetFileExists file -> fileExistsSlow vfs file
244244

245-
fileExistsSlow :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, ([a], Maybe Bool))
245+
fileExistsSlow :: VFSHandle -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe Bool)
246246
fileExistsSlow vfs file = do
247247
-- See Note [Invalidating file existence results]
248248
alwaysRerun
249249
exist <- liftIO $ getFileExistsVFS vfs file
250-
pure (summarizeExists exist, ([], Just exist))
250+
pure (summarizeExists exist, Just exist)
251251

252252
getFileExistsVFS :: VFSHandle -> NormalizedFilePath -> IO Bool
253253
getFileExistsVFS vfs file = do

ghcide/src/Development/IDE/Core/FileStore.hs

Lines changed: 38 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,12 @@ module Development.IDE.Core.FileStore(
1414
VFSHandle,
1515
makeVFSHandle,
1616
makeLSPVFSHandle,
17-
isFileOfInterestRule
18-
,resetFileStore
19-
,resetInterfaceStore
17+
isFileOfInterestRule,
18+
resetFileStore,
19+
resetInterfaceStore,
20+
getModificationTimeImpl,
21+
addIdeGlobal,
22+
getFileContentsImpl
2023
) where
2124

2225
import Control.Concurrent.Extra
@@ -33,7 +36,8 @@ import Data.Maybe
3336
import qualified Data.Rope.UTF16 as Rope
3437
import qualified Data.Text as T
3538
import Data.Time
36-
import Development.IDE.Core.OfInterest (getFilesOfInterest, OfInterestVar(..))
39+
import Development.IDE.Core.OfInterest (OfInterestVar (..),
40+
getFilesOfInterest)
3741
import Development.IDE.Core.RuleTypes
3842
import Development.IDE.Core.Shake
3943
import Development.IDE.GHC.Orphans ()
@@ -67,7 +71,9 @@ import Language.LSP.Server hiding
6771
import qualified Language.LSP.Server as LSP
6872
import Language.LSP.Types (FileChangeType (FcChanged),
6973
FileEvent (FileEvent),
70-
uriToFilePath, toNormalizedFilePath)
74+
NormalizedFilePath (NormalizedFilePath),
75+
toNormalizedFilePath,
76+
uriToFilePath)
7177
import Language.LSP.VFS
7278
import System.FilePath
7379

@@ -94,14 +100,22 @@ makeLSPVFSHandle lspEnv = VFSHandle
94100

95101

96102
isFileOfInterestRule :: Rules ()
97-
isFileOfInterestRule = defineEarlyCutoff $ \IsFileOfInterest f -> do
103+
isFileOfInterestRule = defineEarlyCutoff $ RuleNoDiagnostics $ \IsFileOfInterest f -> do
98104
filesOfInterest <- getFilesOfInterest
99105
let res = maybe NotFOI IsFOI $ f `HM.lookup` filesOfInterest
100-
return (Just $ BS.pack $ show $ hash res, ([], Just res))
106+
return (Just $ BS.pack $ show $ hash res, Just res)
101107

102108
getModificationTimeRule :: VFSHandle -> (NormalizedFilePath -> Action Bool) -> Rules ()
103-
getModificationTimeRule vfs isWatched =
104-
defineEarlyCutoff $ \(GetModificationTime_ missingFileDiags) file -> do
109+
getModificationTimeRule vfs isWatched = defineEarlyCutoff $ Rule $ \(GetModificationTime_ missingFileDiags) file ->
110+
getModificationTimeImpl vfs isWatched missingFileDiags file
111+
112+
getModificationTimeImpl :: VFSHandle
113+
-> (NormalizedFilePath -> Action Bool)
114+
-> Bool
115+
-> NormalizedFilePath
116+
-> Action
117+
(Maybe BS.ByteString, ([FileDiagnostic], Maybe FileVersion))
118+
getModificationTimeImpl vfs isWatched missingFileDiags file = do
105119
let file' = fromNormalizedFilePath file
106120
let wrap time@(l,s) = (Just $ BS.pack $ show time, ([], Just $ ModificationTime l s))
107121
mbVirtual <- liftIO $ getVirtualFile vfs $ filePathToUri' file
@@ -196,16 +210,21 @@ internalTimeToUTCTime large small =
196210
#endif
197211

198212
getFileContentsRule :: VFSHandle -> Rules ()
199-
getFileContentsRule vfs =
200-
define $ \GetFileContents file -> do
201-
-- need to depend on modification time to introduce a dependency with Cutoff
202-
time <- use_ GetModificationTime file
203-
res <- liftIO $ ideTryIOException file $ do
204-
mbVirtual <- getVirtualFile vfs $ filePathToUri' file
205-
pure $ Rope.toText . _text <$> mbVirtual
206-
case res of
207-
Left err -> return ([err], Nothing)
208-
Right contents -> return ([], Just (time, contents))
213+
getFileContentsRule vfs = define $ \GetFileContents file -> getFileContentsImpl vfs file
214+
215+
getFileContentsImpl
216+
:: VFSHandle
217+
-> NormalizedFilePath
218+
-> Action ([FileDiagnostic], Maybe (FileVersion, Maybe T.Text))
219+
getFileContentsImpl vfs file = do
220+
-- need to depend on modification time to introduce a dependency with Cutoff
221+
time <- use_ GetModificationTime file
222+
res <- liftIO $ ideTryIOException file $ do
223+
mbVirtual <- getVirtualFile vfs $ filePathToUri' file
224+
pure $ Rope.toText . _text <$> mbVirtual
225+
case res of
226+
Left err -> return ([err], Nothing)
227+
Right contents -> return ([], Just (time, contents))
209228

210229
ideTryIOException :: NormalizedFilePath -> IO a -> IO (Either FileDiagnostic a)
211230
ideTryIOException fp act =

ghcide/src/Development/IDE/Core/OfInterest.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -56,10 +56,10 @@ instance Binary GetFilesOfInterest
5656
ofInterestRules :: Rules ()
5757
ofInterestRules = do
5858
addIdeGlobal . OfInterestVar =<< liftIO (newVar HashMap.empty)
59-
defineEarlyCutoff $ \GetFilesOfInterest _file -> assert (null $ fromNormalizedFilePath _file) $ do
59+
defineEarlyCutoff $ RuleNoDiagnostics $ \GetFilesOfInterest _file -> assert (null $ fromNormalizedFilePath _file) $ do
6060
alwaysRerun
6161
filesOfInterest <- getFilesOfInterestUntracked
62-
pure (Just $ BS.fromString $ show filesOfInterest, ([], Just filesOfInterest))
62+
pure (Just $ BS.fromString $ show filesOfInterest, Just filesOfInterest)
6363

6464

6565
-- | Get the files that are open in the IDE.

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 24 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -169,13 +169,13 @@ usesE :: IdeRule k v => k -> [NormalizedFilePath] -> MaybeT IdeAction [(v,Positi
169169
usesE k = MaybeT . fmap sequence . mapM (useWithStaleFast k)
170170

171171
defineNoFile :: IdeRule k v => (k -> Action v) -> Rules ()
172-
defineNoFile f = define $ \k file -> do
173-
if file == emptyFilePath then do res <- f k; return ([], Just res) else
172+
defineNoFile f = defineNoDiagnostics $ \k file -> do
173+
if file == emptyFilePath then do res <- f k; return (Just res) else
174174
fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file"
175175

176176
defineEarlyCutOffNoFile :: IdeRule k v => (k -> Action (BS.ByteString, v)) -> Rules ()
177-
defineEarlyCutOffNoFile f = defineEarlyCutoff $ \k file -> do
178-
if file == emptyFilePath then do (hash, res) <- f k; return (Just hash, ([], Just res)) else
177+
defineEarlyCutOffNoFile f = defineEarlyCutoff $ RuleNoDiagnostics $ \k file -> do
178+
if file == emptyFilePath then do (hash, res) <- f k; return (Just hash, Just res) else
179179
fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file"
180180

181181
------------------------------------------------------------
@@ -308,7 +308,7 @@ priorityFilesOfInterest = Priority (-2)
308308
-- and https://github.com/mpickering/ghcide/pull/22#issuecomment-625070490
309309
-- GHC wiki about: https://gitlab.haskell.org/ghc/ghc/-/wikis/api-annotations
310310
getParsedModuleRule :: Rules ()
311-
getParsedModuleRule = defineEarlyCutoff $ \GetParsedModule file -> do
311+
getParsedModuleRule = defineEarlyCutoff $ Rule $ \GetParsedModule file -> do
312312
ModSummaryResult{msrModSummary = ms} <- use_ GetModSummary file
313313
sess <- use_ GhcSession file
314314
let hsc = hscEnv sess
@@ -372,8 +372,9 @@ mergeParseErrorsHaddock normal haddock = normal ++
372372
-- | This rule provides a ParsedModule preserving all annotations,
373373
-- including keywords, punctuation and comments.
374374
-- So it is suitable for use cases where you need a perfect edit.
375+
-- FIXME this rule should probably not produce diagnostics
375376
getParsedModuleWithCommentsRule :: Rules ()
376-
getParsedModuleWithCommentsRule = defineEarlyCutoff $ \GetParsedModuleWithComments file -> do
377+
getParsedModuleWithCommentsRule = defineEarlyCutoff $ Rule $ \GetParsedModuleWithComments file -> do
377378
ModSummaryResult{msrModSummary = ms} <- use_ GetModSummary file
378379
sess <- use_ GhcSession file
379380
opt <- getIdeOptions
@@ -569,13 +570,13 @@ reportImportCyclesRule =
569570
-- NOTE: result does not include the argument file.
570571
getDependenciesRule :: Rules ()
571572
getDependenciesRule =
572-
defineEarlyCutoff $ \GetDependencies file -> do
573+
defineEarlyCutoff $ RuleNoDiagnostics $ \GetDependencies file -> do
573574
depInfo <- use_ GetDependencyInformation file
574575
let allFiles = reachableModules depInfo
575576
_ <- uses_ ReportImportCycles allFiles
576577
opts <- getIdeOptions
577578
let mbFingerprints = map (fingerprintString . fromNormalizedFilePath) allFiles <$ optShakeFiles opts
578-
return (fingerprintToBS . fingerprintFingerprints <$> mbFingerprints, ([], transitiveDeps depInfo file))
579+
return (fingerprintToBS . fingerprintFingerprints <$> mbFingerprints, transitiveDeps depInfo file)
579580

580581
getHieAstsRule :: Rules ()
581582
getHieAstsRule =
@@ -739,7 +740,7 @@ loadGhcSession = do
739740
let fingerprint = hash (sessionVersion res)
740741
return (BS.pack (show fingerprint), res)
741742

742-
defineEarlyCutoff $ \GhcSession file -> do
743+
defineEarlyCutoff $ Rule $ \GhcSession file -> do
743744
IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO
744745
(val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file
745746

@@ -790,7 +791,7 @@ ghcSessionDepsDefinition file = do
790791
-- | Load a iface from disk, or generate it if there isn't one or it is out of date
791792
-- This rule also ensures that the `.hie` and `.o` (if needed) files are written out.
792793
getModIfaceFromDiskRule :: Rules ()
793-
getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
794+
getModIfaceFromDiskRule = defineEarlyCutoff $ Rule $ \GetModIfaceFromDisk f -> do
794795
ms <- msrModSummary <$> use_ GetModSummary f
795796
(diags_session, mb_session) <- ghcSessionDepsDefinition f
796797
case mb_session of
@@ -814,7 +815,7 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
814815
-- disk since we are careful to write out the `.hie` file before writing the
815816
-- `.hi` file
816817
getModIfaceFromDiskAndIndexRule :: Rules ()
817-
getModIfaceFromDiskAndIndexRule = defineEarlyCutoff $ \GetModIfaceFromDiskAndIndex f -> do
818+
getModIfaceFromDiskAndIndexRule = defineEarlyCutoff $ RuleNoDiagnostics $ \GetModIfaceFromDiskAndIndex f -> do
818819
x <- use_ GetModIfaceFromDisk f
819820
se@ShakeExtras{hiedb} <- getShakeExtras
820821

@@ -844,10 +845,10 @@ getModIfaceFromDiskAndIndexRule = defineEarlyCutoff $ \GetModIfaceFromDiskAndInd
844845
indexHieFile se ms f hash hf
845846

846847
let fp = hiFileFingerPrint x
847-
return (Just fp, ([], Just x))
848+
return (Just fp, Just x)
848849

849850
isHiFileStableRule :: Rules ()
850-
isHiFileStableRule = defineEarlyCutoff $ \IsHiFileStable f -> do
851+
isHiFileStableRule = defineEarlyCutoff $ RuleNoDiagnostics $ \IsHiFileStable f -> do
851852
ms <- msrModSummary <$> use_ GetModSummaryWithoutTimestamps f
852853
let hiFile = toNormalizedFilePath'
853854
$ ml_hi_file $ ms_location ms
@@ -865,11 +866,11 @@ isHiFileStableRule = defineEarlyCutoff $ \IsHiFileStable f -> do
865866
pure $ if all (== SourceUnmodifiedAndStable) deps
866867
then SourceUnmodifiedAndStable
867868
else SourceUnmodified
868-
return (Just (BS.pack $ show sourceModified), ([], Just sourceModified))
869+
return (Just (BS.pack $ show sourceModified), Just sourceModified)
869870

870871
getModSummaryRule :: Rules ()
871872
getModSummaryRule = do
872-
defineEarlyCutoff $ \GetModSummary f -> do
873+
defineEarlyCutoff $ Rule $ \GetModSummary f -> do
873874
session <- hscEnv <$> use_ GhcSession f
874875
(modTime, mFileContent) <- getFileContents f
875876
let fp = fromNormalizedFilePath f
@@ -884,7 +885,7 @@ getModSummaryRule = do
884885
return ( Just (fingerprintToBS fingerPrint) , ([], Just res))
885886
Left diags -> return (Nothing, (diags, Nothing))
886887

887-
defineEarlyCutoff $ \GetModSummaryWithoutTimestamps f -> do
888+
defineEarlyCutoff $ RuleNoDiagnostics $ \GetModSummaryWithoutTimestamps f -> do
888889
ms <- use GetModSummary f
889890
case ms of
890891
Just res@ModSummaryResult{..} -> do
@@ -893,8 +894,8 @@ getModSummaryRule = do
893894
ms_hspp_buf = error "use GetModSummary instead of GetModSummaryWithoutTimestamps"
894895
}
895896
fp = fingerprintToBS msrFingerprint
896-
return (Just fp, ([], Just res{msrModSummary = ms}))
897-
Nothing -> return (Nothing, ([], Nothing))
897+
return (Just fp, Just res{msrModSummary = ms})
898+
Nothing -> return (Nothing, Nothing)
898899

899900
generateCore :: RunSimplifier -> NormalizedFilePath -> Action (IdeResult ModGuts)
900901
generateCore runSimplifier file = do
@@ -908,7 +909,7 @@ generateCoreRule =
908909
define $ \GenerateCore -> generateCore (RunSimplifier True)
909910

910911
getModIfaceRule :: Rules ()
911-
getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
912+
getModIfaceRule = defineEarlyCutoff $ Rule $ \GetModIface f -> do
912913
fileOfInterest <- use_ IsFileOfInterest f
913914
res@(_,(_,mhmi)) <- case fileOfInterest of
914915
IsFOI status -> do
@@ -937,11 +938,11 @@ getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
937938
pure res
938939

939940
getModIfaceWithoutLinkableRule :: Rules ()
940-
getModIfaceWithoutLinkableRule = defineEarlyCutoff $ \GetModIfaceWithoutLinkable f -> do
941+
getModIfaceWithoutLinkableRule = defineEarlyCutoff $ RuleNoDiagnostics $ \GetModIfaceWithoutLinkable f -> do
941942
mhfr <- use GetModIface f
942943
let mhfr' = fmap (\x -> x{ hirHomeMod = (hirHomeMod x){ hm_linkable = Just (error msg) } }) mhfr
943944
msg = "tried to look at linkable for GetModIfaceWithoutLinkable for " ++ show f
944-
pure (fingerprintToBS . getModuleHash . hirModIface <$> mhfr', ([],mhfr'))
945+
pure (fingerprintToBS . getModuleHash . hirModIface <$> mhfr', mhfr')
945946

946947
-- | Also generates and indexes the `.hie` file, along with the `.o` file if needed
947948
-- Invariant maintained is that if the `.hi` file was successfully written, then the
@@ -1037,7 +1038,7 @@ getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType)
10371038
getLinkableType f = use_ NeedsCompilation f
10381039

10391040
needsCompilationRule :: Rules ()
1040-
needsCompilationRule = defineEarlyCutoff $ \NeedsCompilation file -> do
1041+
needsCompilationRule = defineEarlyCutoff $ RuleNoDiagnostics $ \NeedsCompilation file -> do
10411042
graph <- useNoFile GetModuleGraph
10421043
res <- case graph of
10431044
-- Treat as False if some reverse dependency header fails to parse
@@ -1061,7 +1062,7 @@ needsCompilationRule = defineEarlyCutoff $ \NeedsCompilation file -> do
10611062
(uses NeedsCompilation revdeps)
10621063
pure $ computeLinkableType ms modsums (map join needsComps)
10631064

1064-
pure (Just $ BS.pack $ show $ hash res, ([], Just res))
1065+
pure (Just $ BS.pack $ show $ hash res, Just res)
10651066
where
10661067
uses_th_qq (ms_hspp_opts -> dflags) =
10671068
xopt LangExt.TemplateHaskell dflags || xopt LangExt.QuasiQuotes dflags

0 commit comments

Comments
 (0)