@@ -78,6 +78,8 @@ import Control.Concurrent.Async (concurrently)
78
78
import Control.Monad.State
79
79
import System.IO.Error (isDoesNotExistError )
80
80
import Control.Exception.Safe (IOException , catch )
81
+ import FastString (FastString (uniq ))
82
+ import qualified HeaderInfo as Hdr
81
83
82
84
-- | This is useful for rules to convert rules that can only produce errors or
83
85
-- a result into the more general IdeResult type that supports producing
@@ -443,30 +445,30 @@ getSpanInfoRule =
443
445
define $ \ GetSpanInfo file -> do
444
446
tc <- use_ TypeCheck file
445
447
packageState <- hscEnv <$> use_ GhcSession file
446
- deps <- maybe (TransitiveDependencies [] [] [] ) fst <$> useWithStale GetDependencies file
447
- let tdeps = transitiveModuleDeps deps
448
448
449
449
-- When possible, rely on the haddocks embedded in our interface files
450
450
-- This creates problems on ghc-lib, see comment on 'getDocumentationTryGhc'
451
451
#if MIN_GHC_API_VERSION(8,6,0) && !defined(GHC_LIB)
452
452
let parsedDeps = []
453
453
#else
454
+ deps <- maybe (TransitiveDependencies [] [] [] ) fst <$> useWithStale GetDependencies file
455
+ let tdeps = transitiveModuleDeps deps
454
456
parsedDeps <- mapMaybe (fmap fst ) <$> usesWithStale GetParsedModule tdeps
455
457
#endif
456
458
457
- ifaces <- mapMaybe (fmap fst ) <$> usesWithStale GetModIface tdeps
458
459
(fileImports, _) <- use_ GetLocatedImports file
459
460
let imports = second (fmap artifactFilePath) <$> fileImports
460
- x <- liftIO $ getSrcSpanInfos packageState imports tc parsedDeps ( map hirModIface ifaces)
461
+ x <- liftIO $ getSrcSpanInfos packageState imports tc parsedDeps
461
462
return ([] , Just x)
462
463
463
464
-- Typechecks a module.
464
465
typeCheckRule :: Rules ()
465
466
typeCheckRule = define $ \ TypeCheck file -> do
466
467
pm <- use_ GetParsedModule file
468
+ hsc <- hscEnv <$> use_ GhcSessionDeps file
467
469
-- do not generate interface files as this rule is called
468
470
-- for files of interest on every keystroke
469
- typeCheckRuleDefinition file pm SkipGenerationOfInterfaceFiles
471
+ typeCheckRuleDefinition hsc pm SkipGenerationOfInterfaceFiles
470
472
471
473
data GenerateInterfaceFiles
472
474
= DoGenerateInterfaceFiles
@@ -478,29 +480,16 @@ data GenerateInterfaceFiles
478
480
-- garbage collect all the intermediate typechecked modules rather than
479
481
-- retain the information forever in the shake graph.
480
482
typeCheckRuleDefinition
481
- :: NormalizedFilePath -- ^ Path to source file
483
+ :: HscEnv
482
484
-> ParsedModule
483
485
-> GenerateInterfaceFiles -- ^ Should generate .hi and .hie files ?
484
486
-> Action (IdeResult TcModuleResult )
485
- typeCheckRuleDefinition file pm generateArtifacts = do
486
- deps <- use_ GetDependencies file
487
- hsc <- hscEnv <$> use_ GhcSession file
488
- -- Figure out whether we need TemplateHaskell or QuasiQuotes support
489
- let graph_needs_th_qq = needsTemplateHaskellOrQQ $ hsc_mod_graph hsc
490
- file_uses_th_qq = uses_th_qq $ ms_hspp_opts (pm_mod_summary pm)
491
- any_uses_th_qq = graph_needs_th_qq || file_uses_th_qq
492
- mirs <- uses_ GetModIface (transitiveModuleDeps deps)
493
- bytecodes <- if any_uses_th_qq
494
- then -- If we use TH or QQ, we must obtain the bytecode
495
- fmap Just <$> uses_ GenerateByteCode (transitiveModuleDeps deps)
496
- else
497
- pure $ repeat Nothing
498
-
487
+ typeCheckRuleDefinition hsc pm generateArtifacts = do
499
488
setPriority priorityTypeCheck
500
489
IdeOptions { optDefer = defer } <- getIdeOptions
501
490
502
491
addUsageDependencies $ liftIO $ do
503
- res <- typecheckModule defer hsc ( zipWith unpack mirs bytecodes) pm
492
+ res <- typecheckModule defer hsc pm
504
493
case res of
505
494
(diags, Just (hsc,tcm)) | DoGenerateInterfaceFiles <- generateArtifacts -> do
506
495
diagsHie <- generateAndWriteHieFile hsc (tmrModule tcm)
@@ -509,10 +498,6 @@ typeCheckRuleDefinition file pm generateArtifacts = do
509
498
(diags, res) ->
510
499
return (diags, snd <$> res)
511
500
where
512
- unpack HiFileResult {.. } bc = (hirModSummary, (hirModIface, bc))
513
- uses_th_qq dflags =
514
- xopt LangExt. TemplateHaskell dflags || xopt LangExt. QuasiQuotes dflags
515
-
516
501
addUsageDependencies :: Action (a , Maybe TcModuleResult ) -> Action (a , Maybe TcModuleResult )
517
502
addUsageDependencies a = do
518
503
r@ (_, mtc) <- a
@@ -588,6 +573,43 @@ loadGhcSession = do
588
573
Nothing -> BS. pack (show (hash (snd val)))
589
574
return (Just cutoffHash, val)
590
575
576
+ define $ \ GhcSessionDeps file -> ghcSessionDepsDefinition file
577
+
578
+ ghcSessionDepsDefinition :: NormalizedFilePath -> Action (IdeResult HscEnvEq )
579
+ ghcSessionDepsDefinition file = do
580
+ hsc <- hscEnv <$> use_ GhcSession file
581
+ (ms,_) <- useWithStale_ GetModSummary file
582
+ (deps,_) <- useWithStale_ GetDependencies file
583
+ let tdeps = transitiveModuleDeps deps
584
+ ifaces <- uses_ GetModIface tdeps
585
+
586
+ -- Figure out whether we need TemplateHaskell or QuasiQuotes support
587
+ let graph_needs_th_qq = needsTemplateHaskellOrQQ $ hsc_mod_graph hsc
588
+ file_uses_th_qq = uses_th_qq $ ms_hspp_opts ms
589
+ any_uses_th_qq = graph_needs_th_qq || file_uses_th_qq
590
+
591
+ bytecodes <- if any_uses_th_qq
592
+ then -- If we use TH or QQ, we must obtain the bytecode
593
+ fmap Just <$> uses_ GenerateByteCode (transitiveModuleDeps deps)
594
+ else
595
+ pure $ repeat Nothing
596
+
597
+ -- Currently GetDependencies returns things in topological order so A comes before B if A imports B.
598
+ -- We need to reverse this as GHC gets very unhappy otherwise and complains about broken interfaces.
599
+ -- Long-term we might just want to change the order returned by GetDependencies
600
+ let inLoadOrder = reverse (zipWith unpack ifaces bytecodes)
601
+
602
+ (session',_) <- liftIO $ runGhcEnv hsc $ do
603
+ setupFinderCache (map hirModSummary ifaces)
604
+ mapM_ (uncurry loadDepModule) inLoadOrder
605
+
606
+ res <- liftIO $ newHscEnvEq session' []
607
+ return ([] , Just res)
608
+ where
609
+ unpack HiFileResult {.. } bc = (hirModIface, bc)
610
+ uses_th_qq dflags =
611
+ xopt LangExt. TemplateHaskell dflags || xopt LangExt. QuasiQuotes dflags
612
+
591
613
getModIfaceFromDiskRule :: Rules ()
592
614
getModIfaceFromDiskRule = defineEarlyCutoff $ \ GetModIfaceFromDisk f -> do
593
615
-- get all dependencies interface files, to check for freshness
@@ -623,12 +645,33 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
623
645
pure (Nothing , ([] , Nothing ))
624
646
625
647
getModSummaryRule :: Rules ()
626
- getModSummaryRule = define $ \ GetModSummary f -> do
648
+ getModSummaryRule = defineEarlyCutoff $ \ GetModSummary f -> do
627
649
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
628
650
(_, mFileContent) <- getFileContents f
629
651
modS <- liftIO $ evalWithDynFlags dflags $ runExceptT $
630
652
getModSummaryFromImports (fromNormalizedFilePath f) (textToStringBuffer <$> mFileContent)
631
- return $ either (,Nothing ) (([] , ) . Just ) modS
653
+ case modS of
654
+ Right ms -> do
655
+ -- Clear the contents as no longer needed
656
+ let ! ms' = ms{ms_hspp_buf= Nothing }
657
+ return ( Just (computeFingerprint f dflags ms), ([] , Just ms'))
658
+ Left diags -> return (Nothing , (diags, Nothing ))
659
+ where
660
+ -- Compute a fingerprint from the contents of `ModSummary`,
661
+ -- eliding the timestamps and other non relevant fields.
662
+ computeFingerprint f dflags ModSummary {.. } =
663
+ let fingerPrint =
664
+ ( moduleNameString (moduleName ms_mod)
665
+ , ms_hspp_file
666
+ , map unLoc opts
667
+ , ml_hs_file ms_location
668
+ , fingerPrintImports ms_srcimps
669
+ , fingerPrintImports ms_textual_imps
670
+ )
671
+ fingerPrintImports = map (fmap uniq *** (moduleNameString . unLoc))
672
+ opts = Hdr. getOptions dflags (fromJust ms_hspp_buf) (fromNormalizedFilePath f)
673
+ fp = hash fingerPrint
674
+ in BS. pack (show fp)
632
675
633
676
getModIfaceRule :: Rules ()
634
677
getModIfaceRule = define $ \ GetModIface f -> do
@@ -667,10 +710,16 @@ getModIfaceRule = define $ \GetModIface f -> do
667
710
case mb_pm of
668
711
Nothing -> return (diags, Nothing )
669
712
Just pm -> do
670
- (diags', tmr) <- typeCheckRuleDefinition f pm DoGenerateInterfaceFiles
671
- -- Bang pattern is important to avoid leaking 'tmr'
672
- let ! res = extract tmr
673
- return (diags <> diags', res)
713
+ -- We want GhcSessionDeps cache objects only for files of interest
714
+ -- As that's no the case here, call the implementation directly
715
+ (diags, mb_hsc) <- ghcSessionDepsDefinition f
716
+ case mb_hsc of
717
+ Nothing -> return (diags, Nothing )
718
+ Just hsc -> do
719
+ (diags', tmr) <- typeCheckRuleDefinition (hscEnv hsc) pm DoGenerateInterfaceFiles
720
+ -- Bang pattern is important to avoid leaking 'tmr'
721
+ let ! res = extract tmr
722
+ return (diags <> diags', res)
674
723
where
675
724
extract Nothing = Nothing
676
725
extract (Just tmr) =
0 commit comments