@@ -43,7 +43,7 @@ import Development.IDE.Spans.Calculate
43
43
import Development.IDE.Import.DependencyInformation
44
44
import Development.IDE.Import.FindImports
45
45
import Development.IDE.Core.FileExists
46
- import Development.IDE.Core.FileStore (getFileContents )
46
+ import Development.IDE.Core.FileStore (modificationTime , getFileContents )
47
47
import Development.IDE.Types.Diagnostics as Diag
48
48
import Development.IDE.Types.Location
49
49
import Development.IDE.GHC.Compat hiding (parseModule , typecheckModule )
@@ -86,6 +86,7 @@ import Control.Exception
86
86
import Control.Monad.State
87
87
import FastString (FastString (uniq ))
88
88
import qualified HeaderInfo as Hdr
89
+ import Data.Time (UTCTime (.. ))
89
90
90
91
-- | This is useful for rules to convert rules that can only produce errors or
91
92
-- a result into the more general IdeResult type that supports producing
@@ -165,7 +166,7 @@ getHieFile ide file mod = do
165
166
166
167
getHomeHieFile :: NormalizedFilePath -> MaybeT IdeAction HieFile
167
168
getHomeHieFile f = do
168
- ms <- fst <$> useE GetModSummary f
169
+ ms <- fst <$> useE GetModSummaryWithoutTimestamps f
169
170
let normal_hie_f = toNormalizedFilePath' hie_f
170
171
hie_f = ml_hie_file $ ms_location ms
171
172
@@ -238,10 +239,10 @@ getParsedModuleRule = defineEarlyCutoff $ \GetParsedModule file -> do
238
239
-- parsed module
239
240
comp_pkgs = mapMaybe (fmap fst . mkImportDirs (hsc_dflags hsc)) (deps sess)
240
241
opt <- getIdeOptions
241
- (_ , contents) <- getFileContents file
242
+ (modTime , contents) <- getFileContents file
242
243
243
244
let dflags = hsc_dflags hsc
244
- mainParse = getParsedModuleDefinition hsc opt comp_pkgs file contents
245
+ mainParse = getParsedModuleDefinition hsc opt comp_pkgs file modTime contents
245
246
246
247
-- Parse again (if necessary) to capture Haddock parse errors
247
248
if gopt Opt_Haddock dflags
@@ -250,7 +251,7 @@ getParsedModuleRule = defineEarlyCutoff $ \GetParsedModule file -> do
250
251
else do
251
252
let haddockParse = do
252
253
(_, (! diagsHaddock, _)) <-
253
- getParsedModuleDefinition (withOptHaddock hsc) opt comp_pkgs file contents
254
+ getParsedModuleDefinition (withOptHaddock hsc) opt comp_pkgs file modTime contents
254
255
return diagsHaddock
255
256
256
257
((fingerPrint, (diags, res)), diagsHaddock) <-
@@ -279,9 +280,11 @@ mergeParseErrorsHaddock normal haddock = normal ++
279
280
| otherwise = " Haddock: " <> x
280
281
281
282
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
285
288
case res of
286
289
Nothing -> pure (Nothing , (diag, Nothing ))
287
290
Just (contents, modu) -> do
@@ -293,7 +296,7 @@ getParsedModuleDefinition packageState opt comp_pkgs file contents = do
293
296
getLocatedImportsRule :: Rules ()
294
297
getLocatedImportsRule =
295
298
define $ \ GetLocatedImports file -> do
296
- ms <- use_ GetModSummary file
299
+ ms <- use_ GetModSummaryWithoutTimestamps file
297
300
let imports = [(False , imp) | imp <- ms_textual_imps ms] ++ [(True , imp) | imp <- ms_srcimps ms]
298
301
env_eq <- use_ GhcSession file
299
302
let env = hscEnv env_eq
@@ -339,7 +342,7 @@ rawDependencyInformation fs = do
339
342
-- If we have, just return its Id but don't update any of the state.
340
343
-- Otherwise, we need to process its imports.
341
344
checkAlreadyProcessed f $ do
342
- al <- lift $ modSummaryToArtifactsLocation f <$> use_ GetModSummary f
345
+ al <- lift $ modSummaryToArtifactsLocation f <$> use_ GetModSummaryWithoutTimestamps f
343
346
-- Get a fresh FilePathId for the new file
344
347
fId <- getFreshFid al
345
348
-- Adding an edge to the bootmap so we can make sure to
@@ -450,7 +453,7 @@ reportImportCyclesRule =
450
453
where loc = srcSpanToLocation (getLoc imp)
451
454
fp = toNormalizedFilePath' $ srcSpanToFilename (getLoc imp)
452
455
getModuleName file = do
453
- ms <- use_ GetModSummary file
456
+ ms <- use_ GetModSummaryWithoutTimestamps file
454
457
pure (moduleNameString . moduleName . ms_mod $ ms)
455
458
showCycle mods = T. intercalate " , " (map T. pack mods)
456
459
@@ -608,7 +611,7 @@ loadGhcSession = do
608
611
ghcSessionDepsDefinition :: NormalizedFilePath -> Action (IdeResult HscEnvEq )
609
612
ghcSessionDepsDefinition file = do
610
613
hsc <- hscEnv <$> use_ GhcSession file
611
- (ms,_) <- useWithStale_ GetModSummary file
614
+ (ms,_) <- useWithStale_ GetModSummaryWithoutTimestamps file
612
615
(deps,_) <- useWithStale_ GetDependencies file
613
616
let tdeps = transitiveModuleDeps deps
614
617
ifaces <- uses_ GetModIface tdeps
@@ -657,7 +660,7 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
657
660
658
661
isHiFileStableRule :: Rules ()
659
662
isHiFileStableRule = define $ \ IsHiFileStable f -> do
660
- ms <- use_ GetModSummary f
663
+ ms <- use_ GetModSummaryWithoutTimestamps f
661
664
let hiFile = toNormalizedFilePath'
662
665
$ case ms_hsc_src ms of
663
666
HsBootFile -> addBootSuffix (ml_hi_file $ ms_location ms)
@@ -679,15 +682,29 @@ isHiFileStableRule = define $ \IsHiFileStable f -> do
679
682
return ([] , Just sourceModified)
680
683
681
684
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 ))
691
708
where
692
709
-- Compute a fingerprint from the contents of `ModSummary`,
693
710
-- eliding the timestamps and other non relevant fields.
@@ -702,8 +719,9 @@ getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
702
719
)
703
720
fingerPrintImports = map (fmap uniq *** (moduleNameString . unLoc))
704
721
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)
707
725
708
726
getModIfaceRule :: Rules ()
709
727
getModIfaceRule = defineEarlyCutoff $ \ GetModIface f -> do
@@ -734,14 +752,15 @@ regenerateHiFile sess f = do
734
752
-- these packages as we have already dealt with what they map to.
735
753
comp_pkgs = mapMaybe (fmap fst . mkImportDirs (hsc_dflags hsc)) (deps sess)
736
754
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
740
759
(diags, mb_pm) <- case mb_pm of
741
760
Just _ -> return (diags, mb_pm)
742
761
Nothing -> do
743
762
-- 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
745
764
return (mergeParseErrorsHaddock diagsNoHaddock diags, mb_pm)
746
765
case mb_pm of
747
766
Nothing -> return (diags, Nothing )
0 commit comments