Skip to content

Commit cdfc4b6

Browse files
Avoid excessive retypechecking of TH codebases (#673)
* Hi file stability * fix missing early cutoff in GetModIface * tests for TH reloading * Do not run hlint on test/data * hlints * Fix legacy code path * Update test/exe/Main.hs Co-authored-by: Moritz Kiefer <[email protected]> Co-authored-by: Moritz Kiefer <[email protected]>
1 parent d999084 commit cdfc4b6

File tree

10 files changed

+149
-30
lines changed

10 files changed

+149
-30
lines changed

fmt.sh

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
11
#!/usr/bin/env bash
22
set -eou pipefail
3-
curl -sSL https://raw.github.com/ndmitchell/hlint/master/misc/run.sh | sh -s . --with-group=extra
3+
curl -sSL https://raw.github.com/ndmitchell/hlint/master/misc/run.sh | sh -s src exe bench/exe test/exe --with-group=extra

src/Development/IDE/Core/Compile.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -587,9 +587,6 @@ loadInterface session ms sourceMod regen = do
587587
-- nothing at all has changed. Stability is just
588588
-- the same check that make is doing for us in
589589
-- one-shot mode.
590-
| not (mi_used_th x) || stable
590+
| not (mi_used_th x) || SourceUnmodifiedAndStable == sourceMod
591591
-> return ([], Just $ HiFileResult ms x)
592592
(_reason, _) -> regen
593-
where
594-
-- TODO support stability
595-
stable = False

src/Development/IDE/Core/RuleTypes.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,19 +14,20 @@ module Development.IDE.Core.RuleTypes(
1414
import Control.DeepSeq
1515
import Data.Binary
1616
import Development.IDE.Import.DependencyInformation
17+
import Development.IDE.GHC.Compat
1718
import Development.IDE.GHC.Util
1819
import Data.Hashable
1920
import Data.Typeable
2021
import qualified Data.Set as S
2122
import Development.Shake
2223
import GHC.Generics (Generic)
2324

24-
import GHC
2525
import Module (InstalledUnitId)
26-
import HscTypes (CgGuts, Linkable, HomeModInfo, ModDetails)
26+
import HscTypes (hm_iface, CgGuts, Linkable, HomeModInfo, ModDetails)
2727

2828
import Development.IDE.Spans.Type
2929
import Development.IDE.Import.FindImports (ArtifactsLocation)
30+
import Data.ByteString (ByteString)
3031

3132

3233
-- NOTATION
@@ -67,6 +68,15 @@ data HiFileResult = HiFileResult
6768
, hirModIface :: !ModIface
6869
}
6970

71+
tmr_hiFileResult :: TcModuleResult -> HiFileResult
72+
tmr_hiFileResult tmr = HiFileResult modSummary modIface
73+
where
74+
modIface = hm_iface . tmrModInfo $ tmr
75+
modSummary = tmrModSummary tmr
76+
77+
hiFileFingerPrint :: HiFileResult -> ByteString
78+
hiFileFingerPrint = fingerprintToBS . getModuleHash . hirModIface
79+
7080
instance NFData HiFileResult where
7181
rnf = rwhnf
7282

src/Development/IDE/Core/Rules.hs

Lines changed: 50 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -644,23 +644,37 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
644644
case mb_session of
645645
Nothing -> return (Nothing, (diags_session, Nothing))
646646
Just session -> do
647-
let hiFile = toNormalizedFilePath'
648-
$ case ms_hsc_src ms of
649-
HsBootFile -> addBootSuffix (ml_hi_file $ ms_location ms)
650-
_ -> ml_hi_file $ ms_location ms
651-
mbHiVersion <- use GetModificationTime_{missingFileDiagnostics=False} hiFile
652-
modVersion <- use_ GetModificationTime f
653-
let sourceModified = case mbHiVersion of
654-
Nothing -> SourceModified
655-
Just x -> if modificationTime x >= modificationTime modVersion
656-
then SourceUnmodified else SourceModified
647+
sourceModified <- use_ IsHiFileStable f
657648
r <- loadInterface (hscEnv session) ms sourceModified (regenerateHiFile session f)
658649
case r of
659650
(diags, Just x) -> do
660-
let fp = fingerprintToBS (getModuleHash (hirModIface x))
661-
return (Just fp, (diags <> diags_session, Just x))
651+
let fp = Just (hiFileFingerPrint x)
652+
return (fp, (diags <> diags_session, Just x))
662653
(diags, Nothing) -> return (Nothing, (diags ++ diags_session, Nothing))
663654

655+
isHiFileStableRule :: Rules ()
656+
isHiFileStableRule = define $ \IsHiFileStable f -> do
657+
ms <- use_ GetModSummary f
658+
let hiFile = toNormalizedFilePath'
659+
$ case ms_hsc_src ms of
660+
HsBootFile -> addBootSuffix (ml_hi_file $ ms_location ms)
661+
_ -> ml_hi_file $ ms_location ms
662+
mbHiVersion <- use GetModificationTime_{missingFileDiagnostics=False} hiFile
663+
modVersion <- use_ GetModificationTime f
664+
sourceModified <- case mbHiVersion of
665+
Nothing -> pure SourceModified
666+
Just x ->
667+
if modificationTime x < modificationTime modVersion
668+
then pure SourceModified
669+
else do
670+
(fileImports, _) <- use_ GetLocatedImports f
671+
let imports = fmap artifactFilePath . snd <$> fileImports
672+
deps <- uses_ IsHiFileStable (catMaybes imports)
673+
pure $ if all (== SourceUnmodifiedAndStable) deps
674+
then SourceUnmodifiedAndStable
675+
else SourceUnmodified
676+
return ([], Just sourceModified)
677+
664678
getModSummaryRule :: Rules ()
665679
getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
666680
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
@@ -691,21 +705,25 @@ getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
691705
in BS.pack (show fp)
692706

693707
getModIfaceRule :: Rules ()
694-
getModIfaceRule = define $ \GetModIface f -> do
708+
getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
695709
#if MIN_GHC_API_VERSION(8,6,0) && !defined(GHC_LIB)
696710
fileOfInterest <- use_ IsFileOfInterest f
697711
if fileOfInterest
698712
then do
699713
-- Never load from disk for files of interest
700714
tmr <- use TypeCheck f
701-
return ([], extractHiFileResult tmr)
702-
else
703-
([],) <$> use GetModIfaceFromDisk f
715+
let !hiFile = extractHiFileResult tmr
716+
let fp = hiFileFingerPrint <$> hiFile
717+
return (fp, ([], hiFile))
718+
else do
719+
hiFile <- use GetModIfaceFromDisk f
720+
let fp = hiFileFingerPrint <$> hiFile
721+
return (fp, ([], hiFile))
704722
#else
705723
tm <- use TypeCheck f
706-
let modIface = hm_iface . tmrModInfo <$> tm
707-
modSummary = tmrModSummary <$> tm
708-
return ([], HiFileResult <$> modSummary <*> modIface)
724+
let !hiFile = extractHiFileResult tm
725+
let fp = hiFileFingerPrint <$> hiFile
726+
return (fp, ([], tmr_hiFileResult <$> tm))
709727
#endif
710728

711729
regenerateHiFile :: HscEnvEq -> NormalizedFilePath -> Action ([FileDiagnostic], Maybe HiFileResult)
@@ -738,7 +756,7 @@ extractHiFileResult :: Maybe TcModuleResult -> Maybe HiFileResult
738756
extractHiFileResult Nothing = Nothing
739757
extractHiFileResult (Just tmr) =
740758
-- Bang patterns are important to force the inner fields
741-
Just $! HiFileResult (tmrModSummary tmr) (hm_iface $ tmrModInfo tmr)
759+
Just $! tmr_hiFileResult tmr
742760

743761
isFileOfInterestRule :: Rules ()
744762
isFileOfInterestRule = defineEarlyCutoff $ \IsFileOfInterest f -> do
@@ -763,3 +781,15 @@ mainRule = do
763781
getModIfaceRule
764782
isFileOfInterestRule
765783
getModSummaryRule
784+
isHiFileStableRule
785+
786+
-- | Given the path to a module src file, this rule returns True if the
787+
-- corresponding `.hi` file is stable, that is, if it is newer
788+
-- than the src file, and all its dependencies are stable too.
789+
data IsHiFileStable = IsHiFileStable
790+
deriving (Eq, Show, Typeable, Generic)
791+
instance Hashable IsHiFileStable
792+
instance NFData IsHiFileStable
793+
instance Binary IsHiFileStable
794+
795+
type instance RuleResult IsHiFileStable = SourceModified

src/Development/IDE/GHC/Orphans.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -70,3 +70,8 @@ instance Show HieFile where
7070

7171
instance NFData HieFile where
7272
rnf = rwhnf
73+
74+
deriving instance Eq SourceModified
75+
deriving instance Show SourceModified
76+
instance NFData SourceModified where
77+
rnf = rwhnf

test/data/TH/THA.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
{-# LANGUAGE TemplateHaskell #-}
2+
module THA where
3+
import Language.Haskell.TH
4+
5+
th_a :: DecsQ
6+
th_a = [d| a = () |]

test/data/TH/THB.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
{-# LANGUAGE TemplateHaskell #-}
2+
module THB where
3+
import THA
4+
5+
$th_a
6+

test/data/TH/THC.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
module THC where
2+
import THB
3+
4+
c ::()
5+
c = a

test/data/TH/hie.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
cradle: {direct: {arguments: ["-Wmissing-signatures", "-package template-haskell", "THA", "THB", "THC"]}}

test/exe/Main.hs

Lines changed: 62 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ main :: IO ()
5656
main = do
5757
-- We mess with env vars so run single-threaded.
5858
setEnv "TASTY_NUM_THREADS" "1" True
59-
defaultMainWithRerun $ testGroup "HIE"
59+
defaultMainWithRerun $ testGroup "ghcide"
6060
[ testSession "open close" $ do
6161
doc <- createDoc "Testing.hs" "haskell" ""
6262
void (skipManyTill anyMessage message :: Session WorkDoneProgressCreateRequest)
@@ -1864,8 +1864,43 @@ thTests =
18641864
_ <- createDoc "A.hs" "haskell" sourceA
18651865
_ <- createDoc "B.hs" "haskell" sourceB
18661866
return ()
1867+
, thReloadingTest `xfail` "expect broken (#672)"
18671868
]
18681869

1870+
-- | test that TH is reevaluated on typecheck
1871+
thReloadingTest :: TestTree
1872+
thReloadingTest = testCase "reloading-th-test" $ withoutStackEnv $ runWithExtraFiles "TH" $ \dir -> do
1873+
let aPath = dir </> "THA.hs"
1874+
bPath = dir </> "THB.hs"
1875+
cPath = dir </> "THC.hs"
1876+
1877+
aSource <- liftIO $ readFileUtf8 aPath -- th = [d|a :: ()|]
1878+
bSource <- liftIO $ readFileUtf8 bPath -- $th
1879+
cSource <- liftIO $ readFileUtf8 cPath -- c = a :: ()
1880+
1881+
adoc <- createDoc aPath "haskell" aSource
1882+
bdoc <- createDoc bPath "haskell" bSource
1883+
cdoc <- createDoc cPath "haskell" cSource
1884+
1885+
expectDiagnostics [("THB.hs", [(DsWarning, (4,0), "Top-level binding")])]
1886+
1887+
-- Change th from () to Bool
1888+
let aSource' = T.unlines $ init (T.lines aSource) ++ ["th_a = [d| a = False|]"]
1889+
changeDoc adoc [TextDocumentContentChangeEvent Nothing Nothing aSource']
1890+
-- generate an artificial warning to avoid timing out if the TH change does not propagate
1891+
changeDoc cdoc [TextDocumentContentChangeEvent Nothing Nothing $ cSource <> "\nfoo=()"]
1892+
1893+
-- Check that the change propagates to C
1894+
expectDiagnostics
1895+
[("THC.hs", [(DsError, (4, 4), "Couldn't match expected type '()' with actual type 'Bool'")])
1896+
,("THC.hs", [(DsWarning, (6,0), "Top-level binding")])
1897+
]
1898+
1899+
closeDoc adoc
1900+
closeDoc bdoc
1901+
closeDoc cdoc
1902+
1903+
18691904
completionTests :: TestTree
18701905
completionTests
18711906
= testGroup "completion"
@@ -2389,8 +2424,32 @@ ifaceTests = testGroup "Interface loading tests"
23892424
ifaceErrorTest
23902425
, ifaceErrorTest2
23912426
, ifaceErrorTest3
2427+
, ifaceTHTest
23922428
]
23932429

2430+
-- | test that TH reevaluates across interfaces
2431+
ifaceTHTest :: TestTree
2432+
ifaceTHTest = testCase "iface-th-test" $ withoutStackEnv $ runWithExtraFiles "TH" $ \dir -> do
2433+
let aPath = dir </> "THA.hs"
2434+
bPath = dir </> "THB.hs"
2435+
cPath = dir </> "THC.hs"
2436+
2437+
aSource <- liftIO $ readFileUtf8 aPath -- [TH] a :: ()
2438+
_bSource <- liftIO $ readFileUtf8 bPath -- a :: ()
2439+
cSource <- liftIO $ readFileUtf8 cPath -- c = a :: ()
2440+
2441+
cdoc <- createDoc cPath "haskell" cSource
2442+
2443+
-- Change [TH]a from () to Bool
2444+
liftIO $ writeFileUTF8 aPath (unlines $ init (lines $ T.unpack aSource) ++ ["th_a = [d| a = False|]"])
2445+
2446+
-- Check that the change propogates to C
2447+
changeDoc cdoc [TextDocumentContentChangeEvent Nothing Nothing cSource]
2448+
expectDiagnostics
2449+
[("THC.hs", [(DsError, (4, 4), "Couldn't match expected type '()' with actual type 'Bool'")])
2450+
,("THB.hs", [(DsWarning, (4,0), "Top-level binding")])]
2451+
closeDoc cdoc
2452+
23942453
ifaceErrorTest :: TestTree
23952454
ifaceErrorTest = testCase "iface-error-test-1" $ withoutStackEnv $ runWithExtraFiles "recomp" $ \dir -> do
23962455
let aPath = dir </> "A.hs"
@@ -2629,9 +2688,9 @@ runInDir dir s = do
26292688
conf = defaultConfig
26302689
-- If you uncomment this you can see all logging
26312690
-- which can be quite useful for debugging.
2632-
-- { logStdErr = True, logColor = False }
2691+
-- { logStdErr = True, logColor = False }
26332692
-- If you really want to, you can also see all messages
2634-
-- { logMessages = True, logColor = False }
2693+
-- { logMessages = True, logColor = False }
26352694

26362695
openTestDataDoc :: FilePath -> Session TextDocumentIdentifier
26372696
openTestDataDoc path = do

0 commit comments

Comments
 (0)