Skip to content

Commit 02177b1

Browse files
authored
Populate ms_hs_date in GetModSummary rule (#694)
* Populate ms_hs_date in GetModSummary rule * More faithful ModSummary timestamps * More ModSummary timestamps * Address duplication * Remove a displaced comment
1 parent 4b6e691 commit 02177b1

File tree

6 files changed

+100
-60
lines changed

6 files changed

+100
-60
lines changed

src/Development/IDE/Core/Compile.hs

+13-15
Original file line numberDiff line numberDiff line change
@@ -85,6 +85,7 @@ import Control.DeepSeq (rnf)
8585
import Control.Exception (evaluate)
8686
import Exception (ExceptionMonad)
8787
import TcEnv (tcLookup)
88+
import Data.Time (UTCTime)
8889

8990

9091
-- | Given a string buffer, return the string (after preprocessing) and the 'ParsedModule'.
@@ -93,13 +94,14 @@ parseModule
9394
-> HscEnv
9495
-> [PackageName]
9596
-> FilePath
97+
-> UTCTime
9698
-> Maybe SB.StringBuffer
9799
-> IO (IdeResult (StringBuffer, ParsedModule))
98-
parseModule IdeOptions{..} env comp_pkgs filename mbContents =
100+
parseModule IdeOptions{..} env comp_pkgs filename modTime mbContents =
99101
fmap (either (, Nothing) id) $
100102
evalGhcEnv env $ runExceptT $ do
101103
(contents, dflags) <- preprocessor filename mbContents
102-
(diag, modu) <- parseFileContents optPreprocessor dflags comp_pkgs filename contents
104+
(diag, modu) <- parseFileContents optPreprocessor dflags comp_pkgs filename modTime contents
103105
return (diag, Just (contents, modu))
104106

105107

@@ -409,23 +411,20 @@ getImportsParsed dflags (L loc parsed) = do
409411
getModSummaryFromBuffer
410412
:: GhcMonad m
411413
=> FilePath
414+
-> UTCTime
412415
-> DynFlags
413416
-> GHC.ParsedSource
414417
-> StringBuffer
415418
-> ExceptT [FileDiagnostic] m ModSummary
416-
getModSummaryFromBuffer fp dflags parsed contents = do
419+
getModSummaryFromBuffer fp modTime dflags parsed contents = do
417420
(modName, imports) <- liftEither $ getImportsParsed dflags parsed
418421

419422
modLoc <- liftIO $ mkHomeModLocation dflags modName fp
420423
let InstalledUnitId unitId = thisInstalledUnitId dflags
421424
return $ ModSummary
422425
{ ms_mod = mkModule (fsToUnitId unitId) modName
423426
, ms_location = modLoc
424-
, ms_hs_date = error "Rules should not depend on ms_hs_date"
425-
-- When we are working with a virtual file we do not have a file date.
426-
-- To avoid silent issues where something is not processed because the date
427-
-- has not changed, we make sure that things blow up if they depend on the
428-
-- date.
427+
, ms_hs_date = modTime
429428
, ms_textual_imps = [imp | (False, imp) <- imports]
430429
, ms_hspp_file = fp
431430
, ms_hspp_opts = dflags
@@ -455,9 +454,10 @@ getModSummaryFromBuffer fp dflags parsed contents = do
455454
getModSummaryFromImports
456455
:: (HasDynFlags m, ExceptionMonad m, MonadIO m)
457456
=> FilePath
457+
-> UTCTime
458458
-> Maybe SB.StringBuffer
459459
-> ExceptT [FileDiagnostic] m ModSummary
460-
getModSummaryFromImports fp contents = do
460+
getModSummaryFromImports fp modTime contents = do
461461
(contents, dflags) <- preprocessor fp contents
462462
(srcImports, textualImports, L _ moduleName) <-
463463
ExceptT $ liftIO $ first (diagFromErrMsgs "parser" dflags) <$> GHC.getHeaderImports dflags contents fp fp
@@ -476,10 +476,7 @@ getModSummaryFromImports fp contents = do
476476
#if MIN_GHC_API_VERSION(8,8,0)
477477
, ms_hie_date = Nothing
478478
#endif
479-
, ms_hs_date = error "Rules should not depend on ms_hs_date"
480-
-- When we are working with a virtual file we do not have a file date.
481-
-- To avoid silent issues where something is not processed because the date
482-
-- has not changed, we make sure that things blow up if they depend on the date.
479+
, ms_hs_date = modTime
483480
, ms_hsc_src = sourceType
484481
-- The contents are used by the GetModSummary rule
485482
, ms_hspp_buf = Just contents
@@ -536,9 +533,10 @@ parseFileContents
536533
-> DynFlags -- ^ flags to use
537534
-> [PackageName] -- ^ The package imports to ignore
538535
-> FilePath -- ^ the filename (for source locations)
536+
-> UTCTime -- ^ the modification timestamp
539537
-> SB.StringBuffer -- ^ Haskell module source text (full Unicode is supported)
540538
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], ParsedModule)
541-
parseFileContents customPreprocessor dflags comp_pkgs filename contents = do
539+
parseFileContents customPreprocessor dflags comp_pkgs filename modTime contents = do
542540
let loc = mkRealSrcLoc (mkFastString filename) 1 1
543541
case unP Parser.parseModule (mkPState dflags contents loc) of
544542
#if MIN_GHC_API_VERSION(8,10,0)
@@ -572,7 +570,7 @@ parseFileContents customPreprocessor dflags comp_pkgs filename contents = do
572570
unless (null errs) $ throwE $ diagFromStrings "parser" DsError errs
573571
let parsed' = removePackageImports comp_pkgs parsed
574572
let preproc_warnings = diagFromStrings "parser" DsWarning preproc_warns
575-
ms <- getModSummaryFromBuffer filename dflags parsed' contents
573+
ms <- getModSummaryFromBuffer filename modTime dflags parsed' contents
576574
let pm =
577575
ParsedModule {
578576
pm_mod_summary = ms

src/Development/IDE/Core/FileStore.hs

+24-8
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.Core.FileStore(
1010
setFileModified,
1111
setSomethingModified,
1212
fileStoreRules,
13+
modificationTime,
1314
VFSHandle,
1415
makeVFSHandle,
1516
makeLSPVFSHandle
@@ -27,6 +28,8 @@ import Development.Shake.Classes
2728
import Control.Exception
2829
import GHC.Generics
2930
import Data.Either.Extra
31+
import Data.Int (Int64)
32+
import Data.Time
3033
import System.IO.Error
3134
import qualified Data.ByteString.Char8 as BS
3235
import Development.IDE.Types.Diagnostics
@@ -36,9 +39,9 @@ import Development.IDE.Core.RuleTypes
3639
import qualified Data.Rope.UTF16 as Rope
3740

3841
#ifdef mingw32_HOST_OS
39-
import Data.Time
4042
import qualified System.Directory as Dir
4143
#else
44+
import Data.Time.Clock.System (systemToUTCTime, SystemTime(MkSystemTime))
4245
import Foreign.Ptr
4346
import Foreign.C.String
4447
import Foreign.C.Types
@@ -124,7 +127,7 @@ getModificationTimeRule vfs =
124127
-- We might also want to try speeding this up on Windows at some point.
125128
-- TODO leverage DidChangeWatchedFile lsp notifications on clients that
126129
-- support them, as done for GetFileExists
127-
getModTime :: FilePath -> IO (Int,Int)
130+
getModTime :: FilePath -> IO (Int64, Int64)
128131
getModTime f =
129132
#ifdef mingw32_HOST_OS
130133
do time <- Dir.getModificationTime f
@@ -136,15 +139,24 @@ getModificationTimeRule vfs =
136139
alloca $ \secPtr ->
137140
alloca $ \nsecPtr -> do
138141
Posix.throwErrnoPathIfMinus1Retry_ "getmodtime" f $ c_getModTime f' secPtr nsecPtr
139-
sec <- peek secPtr
140-
nsec <- peek nsecPtr
141-
pure (fromEnum sec, fromIntegral nsec)
142+
CTime sec <- peek secPtr
143+
CLong nsec <- peek nsecPtr
144+
pure (sec, nsec)
142145

143146
-- Sadly even unix’s getFileStatus + modificationTimeHiRes is still about twice as slow
144147
-- as doing the FFI call ourselves :(.
145148
foreign import ccall "getmodtime" c_getModTime :: CString -> Ptr CTime -> Ptr CLong -> IO Int
146149
#endif
147150

151+
modificationTime :: FileVersion -> Maybe UTCTime
152+
modificationTime VFSVersion{} = Nothing
153+
modificationTime (ModificationTime large small) =
154+
#ifdef mingw32_HOST_OS
155+
Just (UTCTime (ModifiedJulianDay $ fromIntegral large) (picosecondsToDiffTime $ fromIntegral small))
156+
#else
157+
Just (systemToUTCTime $ MkSystemTime large (fromIntegral small))
158+
#endif
159+
148160
getFileContentsRule :: VFSHandle -> Rules ()
149161
getFileContentsRule vfs =
150162
define $ \GetFileContents file -> do
@@ -163,9 +175,13 @@ ideTryIOException fp act =
163175
(\(e :: IOException) -> ideErrorText fp $ T.pack $ show e)
164176
<$> try act
165177

166-
167-
getFileContents :: NormalizedFilePath -> Action (FileVersion, Maybe T.Text)
168-
getFileContents = use_ GetFileContents
178+
-- | Returns the modification time and the contents.
179+
-- For VFS paths, the modification time is the current time.
180+
getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe T.Text)
181+
getFileContents f = do
182+
(fv, txt) <- use_ GetFileContents f
183+
modTime <- maybe (liftIO getCurrentTime) return $ modificationTime fv
184+
return (modTime, txt)
169185

170186
fileStoreRules :: VFSHandle -> Rules ()
171187
fileStoreRules vfs = do

src/Development/IDE/Core/RuleTypes.hs

+10
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,10 @@ type instance RuleResult IsFileOfInterest = Bool
123123
-- without needing to parse the entire source
124124
type instance RuleResult GetModSummary = ModSummary
125125

126+
-- | Generate a ModSummary with the timestamps elided,
127+
-- for more successful early cutoff
128+
type instance RuleResult GetModSummaryWithoutTimestamps = ModSummary
129+
126130
data GetParsedModule = GetParsedModule
127131
deriving (Eq, Show, Typeable, Generic)
128132
instance Hashable GetParsedModule
@@ -206,6 +210,12 @@ instance Hashable IsFileOfInterest
206210
instance NFData IsFileOfInterest
207211
instance Binary IsFileOfInterest
208212

213+
data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
214+
deriving (Eq, Show, Typeable, Generic)
215+
instance Hashable GetModSummaryWithoutTimestamps
216+
instance NFData GetModSummaryWithoutTimestamps
217+
instance Binary GetModSummaryWithoutTimestamps
218+
209219
data GetModSummary = GetModSummary
210220
deriving (Eq, Show, Typeable, Generic)
211221
instance Hashable GetModSummary

src/Development/IDE/Core/Rules.hs

+47-28
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ import Development.IDE.Spans.Calculate
4343
import Development.IDE.Import.DependencyInformation
4444
import Development.IDE.Import.FindImports
4545
import Development.IDE.Core.FileExists
46-
import Development.IDE.Core.FileStore (getFileContents)
46+
import Development.IDE.Core.FileStore (modificationTime, getFileContents)
4747
import Development.IDE.Types.Diagnostics as Diag
4848
import Development.IDE.Types.Location
4949
import Development.IDE.GHC.Compat hiding (parseModule, typecheckModule)
@@ -86,6 +86,7 @@ import Control.Exception
8686
import Control.Monad.State
8787
import FastString (FastString(uniq))
8888
import qualified HeaderInfo as Hdr
89+
import Data.Time (UTCTime(..))
8990

9091
-- | This is useful for rules to convert rules that can only produce errors or
9192
-- a result into the more general IdeResult type that supports producing
@@ -165,7 +166,7 @@ getHieFile ide file mod = do
165166

166167
getHomeHieFile :: NormalizedFilePath -> MaybeT IdeAction HieFile
167168
getHomeHieFile f = do
168-
ms <- fst <$> useE GetModSummary f
169+
ms <- fst <$> useE GetModSummaryWithoutTimestamps f
169170
let normal_hie_f = toNormalizedFilePath' hie_f
170171
hie_f = ml_hie_file $ ms_location ms
171172

@@ -238,10 +239,10 @@ getParsedModuleRule = defineEarlyCutoff $ \GetParsedModule file -> do
238239
-- parsed module
239240
comp_pkgs = mapMaybe (fmap fst . mkImportDirs (hsc_dflags hsc)) (deps sess)
240241
opt <- getIdeOptions
241-
(_, contents) <- getFileContents file
242+
(modTime, contents) <- getFileContents file
242243

243244
let dflags = hsc_dflags hsc
244-
mainParse = getParsedModuleDefinition hsc opt comp_pkgs file contents
245+
mainParse = getParsedModuleDefinition hsc opt comp_pkgs file modTime contents
245246

246247
-- Parse again (if necessary) to capture Haddock parse errors
247248
if gopt Opt_Haddock dflags
@@ -250,7 +251,7 @@ getParsedModuleRule = defineEarlyCutoff $ \GetParsedModule file -> do
250251
else do
251252
let haddockParse = do
252253
(_, (!diagsHaddock, _)) <-
253-
getParsedModuleDefinition (withOptHaddock hsc) opt comp_pkgs file contents
254+
getParsedModuleDefinition (withOptHaddock hsc) opt comp_pkgs file modTime contents
254255
return diagsHaddock
255256

256257
((fingerPrint, (diags, res)), diagsHaddock) <-
@@ -279,9 +280,11 @@ mergeParseErrorsHaddock normal haddock = normal ++
279280
| otherwise = "Haddock: " <> x
280281

281282

282-
getParsedModuleDefinition :: HscEnv -> IdeOptions -> [PackageName] -> NormalizedFilePath -> Maybe T.Text -> IO (Maybe ByteString, ([FileDiagnostic], Maybe ParsedModule))
283-
getParsedModuleDefinition packageState opt comp_pkgs file contents = do
284-
(diag, res) <- parseModule opt packageState comp_pkgs (fromNormalizedFilePath file) (fmap textToStringBuffer contents)
283+
getParsedModuleDefinition :: HscEnv -> IdeOptions -> [PackageName] -> NormalizedFilePath -> UTCTime -> Maybe T.Text -> IO (Maybe ByteString, ([FileDiagnostic], Maybe ParsedModule))
284+
getParsedModuleDefinition packageState opt comp_pkgs file modTime contents = do
285+
let fp = fromNormalizedFilePath file
286+
buffer = textToStringBuffer <$> contents
287+
(diag, res) <- parseModule opt packageState comp_pkgs fp modTime buffer
285288
case res of
286289
Nothing -> pure (Nothing, (diag, Nothing))
287290
Just (contents, modu) -> do
@@ -293,7 +296,7 @@ getParsedModuleDefinition packageState opt comp_pkgs file contents = do
293296
getLocatedImportsRule :: Rules ()
294297
getLocatedImportsRule =
295298
define $ \GetLocatedImports file -> do
296-
ms <- use_ GetModSummary file
299+
ms <- use_ GetModSummaryWithoutTimestamps file
297300
let imports = [(False, imp) | imp <- ms_textual_imps ms] ++ [(True, imp) | imp <- ms_srcimps ms]
298301
env_eq <- use_ GhcSession file
299302
let env = hscEnv env_eq
@@ -339,7 +342,7 @@ rawDependencyInformation fs = do
339342
-- If we have, just return its Id but don't update any of the state.
340343
-- Otherwise, we need to process its imports.
341344
checkAlreadyProcessed f $ do
342-
al <- lift $ modSummaryToArtifactsLocation f <$> use_ GetModSummary f
345+
al <- lift $ modSummaryToArtifactsLocation f <$> use_ GetModSummaryWithoutTimestamps f
343346
-- Get a fresh FilePathId for the new file
344347
fId <- getFreshFid al
345348
-- Adding an edge to the bootmap so we can make sure to
@@ -450,7 +453,7 @@ reportImportCyclesRule =
450453
where loc = srcSpanToLocation (getLoc imp)
451454
fp = toNormalizedFilePath' $ srcSpanToFilename (getLoc imp)
452455
getModuleName file = do
453-
ms <- use_ GetModSummary file
456+
ms <- use_ GetModSummaryWithoutTimestamps file
454457
pure (moduleNameString . moduleName . ms_mod $ ms)
455458
showCycle mods = T.intercalate ", " (map T.pack mods)
456459

@@ -608,7 +611,7 @@ loadGhcSession = do
608611
ghcSessionDepsDefinition :: NormalizedFilePath -> Action (IdeResult HscEnvEq)
609612
ghcSessionDepsDefinition file = do
610613
hsc <- hscEnv <$> use_ GhcSession file
611-
(ms,_) <- useWithStale_ GetModSummary file
614+
(ms,_) <- useWithStale_ GetModSummaryWithoutTimestamps file
612615
(deps,_) <- useWithStale_ GetDependencies file
613616
let tdeps = transitiveModuleDeps deps
614617
ifaces <- uses_ GetModIface tdeps
@@ -657,7 +660,7 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
657660

658661
isHiFileStableRule :: Rules ()
659662
isHiFileStableRule = define $ \IsHiFileStable f -> do
660-
ms <- use_ GetModSummary f
663+
ms <- use_ GetModSummaryWithoutTimestamps f
661664
let hiFile = toNormalizedFilePath'
662665
$ case ms_hsc_src ms of
663666
HsBootFile -> addBootSuffix (ml_hi_file $ ms_location ms)
@@ -679,15 +682,29 @@ isHiFileStableRule = define $ \IsHiFileStable f -> do
679682
return ([], Just sourceModified)
680683

681684
getModSummaryRule :: Rules ()
682-
getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
683-
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
684-
(_, mFileContent) <- getFileContents f
685-
modS <- liftIO $ evalWithDynFlags dflags $ runExceptT $
686-
getModSummaryFromImports (fromNormalizedFilePath f) (textToStringBuffer <$> mFileContent)
687-
case modS of
688-
Right ms -> do
689-
return ( Just (computeFingerprint f dflags ms), ([], Just ms))
690-
Left diags -> return (Nothing, (diags, Nothing))
685+
getModSummaryRule = do
686+
defineEarlyCutoff $ \GetModSummary f -> do
687+
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
688+
(modTime, mFileContent) <- getFileContents f
689+
let fp = fromNormalizedFilePath f
690+
modS <- liftIO $ evalWithDynFlags dflags $ runExceptT $
691+
getModSummaryFromImports fp modTime (textToStringBuffer <$> mFileContent)
692+
case modS of
693+
Right ms -> do
694+
let fingerPrint = hash (computeFingerprint f dflags ms, hashUTC modTime)
695+
return ( Just (BS.pack $ show fingerPrint) , ([], Just ms))
696+
Left diags -> return (Nothing, (diags, Nothing))
697+
698+
defineEarlyCutoff $ \GetModSummaryWithoutTimestamps f -> do
699+
ms <- use GetModSummary f
700+
case ms of
701+
Just msWithTimestamps -> do
702+
let ms = msWithTimestamps { ms_hs_date = error "use GetModSummary instead of GetModSummaryWithoutTimestamps" }
703+
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
704+
-- include the mod time in the fingerprint
705+
let fp = BS.pack $ show $ hash (computeFingerprint f dflags ms)
706+
return (Just fp, ([], Just ms))
707+
Nothing -> return (Nothing, ([], Nothing))
691708
where
692709
-- Compute a fingerprint from the contents of `ModSummary`,
693710
-- eliding the timestamps and other non relevant fields.
@@ -702,8 +719,9 @@ getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
702719
)
703720
fingerPrintImports = map (fmap uniq *** (moduleNameString . unLoc))
704721
opts = Hdr.getOptions dflags (fromJust ms_hspp_buf) (fromNormalizedFilePath f)
705-
fp = hash fingerPrint
706-
in BS.pack (show fp)
722+
in fingerPrint
723+
724+
hashUTC UTCTime{..} = (fromEnum utctDay, fromEnum utctDayTime)
707725

708726
getModIfaceRule :: Rules ()
709727
getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
@@ -734,14 +752,15 @@ regenerateHiFile sess f = do
734752
-- these packages as we have already dealt with what they map to.
735753
comp_pkgs = mapMaybe (fmap fst . mkImportDirs (hsc_dflags hsc)) (deps sess)
736754
opt <- getIdeOptions
737-
(_, contents) <- getFileContents f
738-
-- Embed --haddocks in the interface file
739-
(_, (diags, mb_pm)) <- liftIO $ getParsedModuleDefinition (withOptHaddock hsc) opt comp_pkgs f contents
755+
(modTime, contents) <- getFileContents f
756+
757+
-- Embed haddocks in the interface file
758+
(_, (diags, mb_pm)) <- liftIO $ getParsedModuleDefinition (withOptHaddock hsc) opt comp_pkgs f modTime contents
740759
(diags, mb_pm) <- case mb_pm of
741760
Just _ -> return (diags, mb_pm)
742761
Nothing -> do
743762
-- if parsing fails, try parsing again with Haddock turned off
744-
(_, (diagsNoHaddock, mb_pm)) <- liftIO $ getParsedModuleDefinition hsc opt comp_pkgs f contents
763+
(_, (diagsNoHaddock, mb_pm)) <- liftIO $ getParsedModuleDefinition hsc opt comp_pkgs f modTime contents
745764
return (mergeParseErrorsHaddock diagsNoHaddock diags, mb_pm)
746765
case mb_pm of
747766
Nothing -> return (diags, Nothing)

0 commit comments

Comments
 (0)