1111--
1212module Development.IDE.Core.Rules (
1313 -- * Types
14- IdeState , GetDependencies ( .. ), GetParsedModule (.. ), TransitiveDependencies (.. ),
14+ IdeState , GetParsedModule (.. ), TransitiveDependencies (.. ),
1515 Priority (.. ), GhcSessionIO (.. ), GetClientSettings (.. ),
1616 -- * Functions
1717 priorityTypeCheck ,
@@ -22,6 +22,7 @@ module Development.IDE.Core.Rules(
2222 defineNoFile ,
2323 defineEarlyCutOffNoFile ,
2424 mainRule ,
25+ RulesConfig (.. ),
2526 getDependencies ,
2627 getParsedModule ,
2728 getParsedModuleWithComments ,
@@ -35,7 +36,6 @@ module Development.IDE.Core.Rules(
3536 getLocatedImportsRule ,
3637 getDependencyInformationRule ,
3738 reportImportCyclesRule ,
38- getDependenciesRule ,
3939 typeCheckRule ,
4040 getDocMapRule ,
4141 loadGhcSession ,
@@ -57,6 +57,7 @@ module Development.IDE.Core.Rules(
5757 ghcSessionDepsDefinition ,
5858 getParsedModuleDefinition ,
5959 typeCheckRuleDefinition ,
60+ GhcSessionDepsConfig (.. ),
6061 ) where
6162
6263#if !MIN_VERSION_ghc(8,8,0)
@@ -139,8 +140,7 @@ import qualified Language.LSP.Server as LSP
139140import Language.LSP.Types (SMethod (SCustomMethod ))
140141import Language.LSP.VFS
141142import System.Directory (canonicalizePath , makeAbsolute )
142-
143- import Data.Default (def )
143+ import Data.Default (def , Default )
144144import Ide.Plugin.Properties (HasProperty ,
145145 KeyNameProxy ,
146146 Properties ,
@@ -149,7 +149,6 @@ import Ide.Plugin.Properties (HasProperty,
149149import Ide.PluginUtils (configForPlugin )
150150import Ide.Types (DynFlagsModifications (dynFlagsModifyGlobal , dynFlagsModifyParser ),
151151 PluginId )
152- import qualified Data.HashSet as HS
153152
154153-- | This is useful for rules to convert rules that can only produce errors or
155154-- a result into the more general IdeResult type that supports producing
@@ -163,7 +162,8 @@ toIdeResult = either (, Nothing) (([],) . Just)
163162-- | Get all transitive file dependencies of a given module.
164163-- Does not include the file itself.
165164getDependencies :: NormalizedFilePath -> Action (Maybe [NormalizedFilePath ])
166- getDependencies file = fmap transitiveModuleDeps <$> use GetDependencies file
165+ getDependencies file =
166+ fmap transitiveModuleDeps . (`transitiveDeps` file) <$> use_ GetDependencyInformation file
167167
168168getSourceFileSource :: NormalizedFilePath -> Action BS. ByteString
169169getSourceFileSource nfp = do
@@ -334,7 +334,7 @@ getLocatedImportsRule =
334334 return $ if itExists then Just nfp' else Nothing
335335 | Just tt <- HM. lookup (TargetModule modName) targets = do
336336 -- reuse the existing NormalizedFilePath in order to maximize sharing
337- let ttmap = HM. mapWithKey const (HS . toMap tt)
337+ let ttmap = HM. mapWithKey const (HashSet . toMap tt)
338338 nfp' = HM. lookupDefault nfp nfp ttmap
339339 itExists <- getFileExists nfp'
340340 return $ if itExists then Just nfp' else Nothing
@@ -492,18 +492,6 @@ reportImportCyclesRule =
492492 pure (moduleNameString . moduleName . ms_mod $ ms)
493493 showCycle mods = T. intercalate " , " (map T. pack mods)
494494
495- -- returns all transitive dependencies in topological order.
496- -- NOTE: result does not include the argument file.
497- getDependenciesRule :: Rules ()
498- getDependenciesRule =
499- defineEarlyCutoff $ RuleNoDiagnostics $ \ GetDependencies file -> do
500- depInfo <- use_ GetDependencyInformation file
501- let allFiles = reachableModules depInfo
502- _ <- uses_ ReportImportCycles allFiles
503- opts <- getIdeOptions
504- let mbFingerprints = map (Util. fingerprintString . fromNormalizedFilePath) allFiles <$ optShakeFiles opts
505- return (fingerprintToBS . Util. fingerprintFingerprints <$> mbFingerprints, transitiveDeps depInfo file)
506-
507495getHieAstsRule :: Rules ()
508496getHieAstsRule =
509497 define $ \ GetHieAst f -> do
@@ -654,8 +642,8 @@ currentLinkables = do
654642 where
655643 go (mod , time) = LM time mod []
656644
657- loadGhcSession :: Rules ()
658- loadGhcSession = do
645+ loadGhcSession :: GhcSessionDepsConfig -> Rules ()
646+ loadGhcSession ghcSessionDepsConfig = do
659647 -- This function should always be rerun because it tracks changes
660648 -- to the version of the collection of HscEnv's.
661649 defineEarlyCutOffNoFile $ \ GhcSessionIO -> do
@@ -691,49 +679,65 @@ loadGhcSession = do
691679 Nothing -> LBS. toStrict $ B. encode (hash (snd val))
692680 return (Just cutoffHash, val)
693681
694- define $ \ GhcSessionDeps file -> ghcSessionDepsDefinition file
695-
696- ghcSessionDepsDefinition :: NormalizedFilePath -> Action (IdeResult HscEnvEq )
697- ghcSessionDepsDefinition file = do
682+ defineNoDiagnostics $ \ GhcSessionDeps file -> do
698683 env <- use_ GhcSession file
699- let hsc = hscEnv env
700- ms <- msrModSummary <$> use_ GetModSummaryWithoutTimestamps file
701- deps <- use_ GetDependencies file
702- let tdeps = transitiveModuleDeps deps
703- uses_th_qq =
704- xopt LangExt. TemplateHaskell dflags || xopt LangExt. QuasiQuotes dflags
705- dflags = ms_hspp_opts ms
706- ifaces <- if uses_th_qq
707- then uses_ GetModIface tdeps
708- else uses_ GetModIfaceWithoutLinkable tdeps
709-
710- -- Currently GetDependencies returns things in topological order so A comes before B if A imports B.
711- -- We need to reverse this as GHC gets very unhappy otherwise and complains about broken interfaces.
712- -- Long-term we might just want to change the order returned by GetDependencies
713- let inLoadOrder = reverse (map hirHomeMod ifaces)
714-
715- session' <- liftIO $ loadModulesHome inLoadOrder <$> setupFinderCache (map hirModSummary ifaces) hsc
716-
717- res <- liftIO $ newHscEnvEqWithImportPaths (envImportPaths env) session' []
718- return ([] , Just res)
684+ ghcSessionDepsDefinition ghcSessionDepsConfig env file
685+
686+ data GhcSessionDepsConfig = GhcSessionDepsConfig
687+ { checkForImportCycles :: Bool
688+ , forceLinkables :: Bool
689+ , fullModSummary :: Bool
690+ }
691+ instance Default GhcSessionDepsConfig where
692+ def = GhcSessionDepsConfig
693+ { checkForImportCycles = True
694+ , forceLinkables = False
695+ , fullModSummary = False
696+ }
697+
698+ ghcSessionDepsDefinition :: GhcSessionDepsConfig -> HscEnvEq -> NormalizedFilePath -> Action (Maybe HscEnvEq )
699+ ghcSessionDepsDefinition GhcSessionDepsConfig {.. } env file = do
700+ let hsc = hscEnv env
701+
702+ mbdeps <- mapM (fmap artifactFilePath . snd ) <$> use_ GetLocatedImports file
703+ case mbdeps of
704+ Nothing -> return Nothing
705+ Just deps -> do
706+ when checkForImportCycles $ void $ uses_ ReportImportCycles deps
707+ ms: mss <- map msrModSummary <$> if fullModSummary
708+ then uses_ GetModSummary (file: deps)
709+ else uses_ GetModSummaryWithoutTimestamps (file: deps)
710+
711+ depSessions <- map hscEnv <$> uses_ GhcSessionDeps deps
712+ let uses_th_qq =
713+ xopt LangExt. TemplateHaskell dflags || xopt LangExt. QuasiQuotes dflags
714+ dflags = ms_hspp_opts ms
715+ ifaces <- if uses_th_qq || forceLinkables
716+ then uses_ GetModIface deps
717+ else uses_ GetModIfaceWithoutLinkable deps
718+
719+ let inLoadOrder = map hirHomeMod ifaces
720+ session' <- liftIO $ mergeEnvs hsc mss inLoadOrder depSessions
721+
722+ Just <$> liftIO (newHscEnvEqWithImportPaths (envImportPaths env) session' [] )
719723
720724-- | Load a iface from disk, or generate it if there isn't one or it is out of date
721725-- This rule also ensures that the `.hie` and `.o` (if needed) files are written out.
722726getModIfaceFromDiskRule :: Rules ()
723727getModIfaceFromDiskRule = defineEarlyCutoff $ Rule $ \ GetModIfaceFromDisk f -> do
724728 ms <- msrModSummary <$> use_ GetModSummary f
725- (diags_session, mb_session) <- ghcSessionDepsDefinition f
729+ mb_session <- use GhcSessionDeps f
726730 case mb_session of
727- Nothing -> return (Nothing , (diags_session , Nothing ))
731+ Nothing -> return (Nothing , ([] , Nothing ))
728732 Just session -> do
729733 sourceModified <- use_ IsHiFileStable f
730734 linkableType <- getLinkableType f
731735 r <- loadInterface (hscEnv session) ms sourceModified linkableType (regenerateHiFile session f ms)
732736 case r of
733- (diags, Nothing ) -> return (Nothing , (diags ++ diags_session , Nothing ))
737+ (diags, Nothing ) -> return (Nothing , (diags, Nothing ))
734738 (diags, Just x) -> do
735739 let ! fp = Just $! hiFileFingerPrint x
736- return (fp, (diags <> diags_session , Just x))
740+ return (fp, (diags, Just x))
737741
738742-- | Check state of hiedb after loading an iface from disk - have we indexed the corresponding `.hie` file?
739743-- This function is responsible for ensuring database consistency
@@ -1055,20 +1059,28 @@ writeHiFileAction hsc hiFile = do
10551059 resetInterfaceStore extras $ toNormalizedFilePath' targetPath
10561060 writeHiFile hsc hiFile
10571061
1062+ data RulesConfig = RulesConfig
1063+ { -- | Disable import cycle checking for improved performance in large codebases
1064+ checkForImportCycles :: Bool
1065+ -- | Disable TH for improved performance in large codebases
1066+ , enableTemplateHaskell :: Bool
1067+ }
1068+
1069+ instance Default RulesConfig where def = RulesConfig True True
1070+
10581071-- | A rule that wires per-file rules together
1059- mainRule :: Rules ()
1060- mainRule = do
1072+ mainRule :: RulesConfig -> Rules ()
1073+ mainRule RulesConfig { .. } = do
10611074 linkables <- liftIO $ newVar emptyModuleEnv
10621075 addIdeGlobal $ CompiledLinkables linkables
10631076 getParsedModuleRule
10641077 getParsedModuleWithCommentsRule
10651078 getLocatedImportsRule
10661079 getDependencyInformationRule
10671080 reportImportCyclesRule
1068- getDependenciesRule
10691081 typeCheckRule
10701082 getDocMapRule
1071- loadGhcSession
1083+ loadGhcSession def{checkForImportCycles}
10721084 getModIfaceFromDiskRule
10731085 getModIfaceFromDiskAndIndexRule
10741086 getModIfaceRule
@@ -1086,8 +1098,10 @@ mainRule = do
10861098 -- * ObjectLinkable -> BCOLinkable : the prev linkable can be reused, signal "no change"
10871099 -- * Object/BCO -> NoLinkable : the prev linkable can be ignored, signal "no change"
10881100 -- * otherwise : the prev linkable cannot be reused, signal "value has changed"
1089- defineEarlyCutoff $ RuleWithCustomNewnessCheck (<=) $ \ NeedsCompilation file ->
1090- needsCompilationRule file
1101+ if enableTemplateHaskell
1102+ then defineEarlyCutoff $ RuleWithCustomNewnessCheck (<=) $ \ NeedsCompilation file ->
1103+ needsCompilationRule file
1104+ else defineNoDiagnostics $ \ NeedsCompilation _ -> return $ Just Nothing
10911105 generateCoreRule
10921106 getImportMapRule
10931107 getAnnotatedParsedSourceRule
0 commit comments