Skip to content

Commit a05a842

Browse files
authored
Avoid always rerunning GetModificationTime for interface files too (#1506)
* Extend file watching to interfaces * Close Shake session before exit in order to dump Shake profile * Update isInterface and resetInterfaceStore with @wz1000 feedback * remove redundant imports
1 parent 2a99031 commit a05a842

File tree

6 files changed

+38
-14
lines changed

6 files changed

+38
-14
lines changed

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

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -115,15 +115,12 @@ import Control.Concurrent.STM hiding (orElse)
115115
import Data.Aeson (toJSON)
116116
import Data.Binary
117117
import Data.Binary.Put
118-
import Data.Bits (shiftR)
119118
import qualified Data.ByteString.Lazy as LBS
120119
import Data.Coerce
121120
import Data.Functor
122121
import qualified Data.HashMap.Strict as HashMap
123122
import Data.Tuple.Extra (dupe)
124123
import Data.Unique
125-
import Data.Word
126-
import Foreign.Marshal.Array (withArrayLen)
127124
import GHC.Fingerprint
128125
import qualified Language.LSP.Server as LSP
129126
import qualified Language.LSP.Types as LSP

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -103,7 +103,7 @@ modifyFileExists state changes = do
103103
modifyVar_ var $ evaluate . HashMap.union changesMap
104104
-- See Note [Invalidating file existence results]
105105
-- flush previous values
106-
mapM_ (deleteValue state GetFileExists) (HashMap.keys changesMap)
106+
mapM_ (deleteValue (shakeExtras state) GetFileExists) (HashMap.keys changesMap)
107107

108108
fromChange :: FileChangeType -> Maybe Bool
109109
fromChange FcCreated = Just True

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

Lines changed: 19 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,9 @@ module Development.IDE.Core.FileStore(
1515
makeVFSHandle,
1616
makeLSPVFSHandle,
1717
isFileOfInterestRule
18-
,resetFileStore) where
18+
,resetFileStore
19+
,resetInterfaceStore
20+
) where
1921

2022
import Control.Concurrent.Extra
2123
import Control.Concurrent.STM (atomically)
@@ -67,6 +69,7 @@ import Language.LSP.Types (FileChangeType (F
6769
FileEvent (FileEvent),
6870
uriToFilePath, toNormalizedFilePath)
6971
import Language.LSP.VFS
72+
import System.FilePath
7073

7174
makeVFSHandle :: IO VFSHandle
7275
makeVFSHandle = do
@@ -111,7 +114,7 @@ getModificationTimeRule vfs isWatched =
111114
pure (Just $ BS.pack $ show ver, ([], Just $ VFSVersion ver))
112115
Nothing -> do
113116
isWF <- isWatched file
114-
unless isWF alwaysRerun
117+
unless (isWF || isInterface file) alwaysRerun
115118
liftIO $ fmap wrap (getModTime file')
116119
`catch` \(e :: IOException) -> do
117120
let err | isDoesNotExistError e = "File does not exist: " ++ file'
@@ -121,6 +124,18 @@ getModificationTimeRule vfs isWatched =
121124
then return (Nothing, ([], Nothing))
122125
else return (Nothing, ([diag], Nothing))
123126

127+
-- | Interface files cannot be watched, since they live outside the workspace.
128+
-- But interface files are private, in that only HLS writes them.
129+
-- So we implement watching ourselves, and bypass the need for alwaysRerun.
130+
isInterface :: NormalizedFilePath -> Bool
131+
isInterface f = takeExtension (fromNormalizedFilePath f) `elem` [".hi", ".hi-boot"]
132+
133+
-- | Reset the GetModificationTime state of interface files
134+
resetInterfaceStore :: ShakeExtras -> NormalizedFilePath -> IO ()
135+
resetInterfaceStore state f = do
136+
deleteValue state (GetModificationTime_ True) f
137+
deleteValue state (GetModificationTime_ False) f
138+
124139
-- | Reset the GetModificationTime state of watched files
125140
resetFileStore :: IdeState -> [FileEvent] -> IO ()
126141
resetFileStore ideState changes = mask $ \_ ->
@@ -134,8 +149,8 @@ resetFileStore ideState changes = mask $ \_ ->
134149
OfInterestVar foisVar <- getIdeGlobalExtras (shakeExtras ideState)
135150
fois <- readVar foisVar
136151
unless (HM.member (toNormalizedFilePath f) fois) $ do
137-
deleteValue ideState (GetModificationTime_ True) (toNormalizedFilePath' f)
138-
deleteValue ideState (GetModificationTime_ False) (toNormalizedFilePath' f)
152+
deleteValue (shakeExtras ideState) (GetModificationTime_ True) (toNormalizedFilePath' f)
153+
deleteValue (shakeExtras ideState) (GetModificationTime_ False) (toNormalizedFilePath' f)
139154
_ -> pure ()
140155

141156
-- Dir.getModificationTime is surprisingly slow since it performs

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

Lines changed: 11 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,7 @@ import Data.Tuple.Extra
8686
import Development.IDE.Core.Compile
8787
import Development.IDE.Core.FileExists
8888
import Development.IDE.Core.FileStore (getFileContents,
89-
modificationTime)
89+
modificationTime, resetInterfaceStore)
9090
import Development.IDE.Core.OfInterest
9191
import Development.IDE.Core.PositionMapping
9292
import Development.IDE.Core.RuleTypes
@@ -922,7 +922,7 @@ getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
922922
hiDiags <- case hiFile of
923923
Just hiFile
924924
| OnDisk <- status
925-
, not (tmrDeferedError tmr) -> liftIO $ writeHiFile hsc hiFile
925+
, not (tmrDeferedError tmr) -> writeHiFileAction hsc hiFile
926926
_ -> pure []
927927
return (fp, (diags++hiDiags, hiFile))
928928
NotFOI -> do
@@ -991,7 +991,7 @@ regenerateHiFile sess f ms compNeeded = do
991991
-- We don't write the `.hi` file if there are defered errors, since we won't get
992992
-- accurate diagnostics next time if we do
993993
hiDiags <- if not $ tmrDeferedError tmr
994-
then liftIO $ writeHiFile hsc hiFile
994+
then writeHiFileAction hsc hiFile
995995
else pure []
996996

997997
pure (hiDiags <> gDiags <> concat wDiags)
@@ -1090,6 +1090,14 @@ needsCompilationRule = defineEarlyCutoff $ \NeedsCompilation file -> do
10901090
newtype CompiledLinkables = CompiledLinkables { getCompiledLinkables :: Var (ModuleEnv UTCTime) }
10911091
instance IsIdeGlobal CompiledLinkables
10921092

1093+
writeHiFileAction :: HscEnv -> HiFileResult -> Action [FileDiagnostic]
1094+
writeHiFileAction hsc hiFile = do
1095+
extras <- getShakeExtras
1096+
let targetPath = ml_hi_file $ ms_location $ hirModSummary hiFile
1097+
liftIO $ do
1098+
resetInterfaceStore extras $ toNormalizedFilePath' targetPath
1099+
writeHiFile hsc hiFile
1100+
10931101
-- | A rule that wires per-file rules together
10941102
mainRule :: Rules ()
10951103
mainRule = do

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -420,11 +420,11 @@ setValues state key file val diags = modifyVar_ state $ \vals -> do
420420
-- | Delete the value stored for a given ide build key
421421
deleteValue
422422
:: (Typeable k, Hashable k, Eq k, Show k)
423-
=> IdeState
423+
=> ShakeExtras
424424
-> k
425425
-> NormalizedFilePath
426426
-> IO ()
427-
deleteValue IdeState{shakeExtras = ShakeExtras{state}} key file = modifyVar_ state $ \vals ->
427+
deleteValue ShakeExtras{state} key file = modifyVar_ state $ \vals ->
428428
evaluate $ HMap.delete (file, Key key) vals
429429

430430
-- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value.

ghcide/src/Development/IDE/LSP/LanguageServer.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -200,7 +200,11 @@ cancelHandler cancelRequest = LSP.notificationHandler SCancelRequest $ \Notifica
200200
liftIO $ cancelRequest (SomeLspId _id)
201201

202202
exitHandler :: IO () -> LSP.Handlers (ServerM c)
203-
exitHandler exit = LSP.notificationHandler SExit (const $ liftIO exit)
203+
exitHandler exit = LSP.notificationHandler SExit $ const $ do
204+
(_, ide) <- ask
205+
-- flush out the Shake session to record a Shake profile if applicable
206+
liftIO $ restartShakeSession (shakeExtras ide) []
207+
liftIO exit
204208

205209
modifyOptions :: LSP.Options -> LSP.Options
206210
modifyOptions x = x{ LSP.textDocumentSync = Just $ tweakTDS origTDS

0 commit comments

Comments
 (0)