@@ -169,13 +169,13 @@ usesE :: IdeRule k v => k -> [NormalizedFilePath] -> MaybeT IdeAction [(v,Positi
169169usesE k = MaybeT . fmap sequence . mapM (useWithStaleFast k)
170170
171171defineNoFile :: IdeRule k v => (k -> Action v ) -> Rules ()
172- defineNoFile f = define $ \ k file -> do
173- if file == emptyFilePath then do res <- f k; return ([] , Just res) else
172+ defineNoFile f = defineNoDiagnostics $ \ k file -> do
173+ if file == emptyFilePath then do res <- f k; return (Just res) else
174174 fail $ " Rule " ++ show k ++ " should always be called with the empty string for a file"
175175
176176defineEarlyCutOffNoFile :: IdeRule k v => (k -> Action (BS. ByteString , v )) -> Rules ()
177- defineEarlyCutOffNoFile f = defineEarlyCutoff $ \ k file -> do
178- if file == emptyFilePath then do (hash, res) <- f k; return (Just hash, ( [] , Just res) ) else
177+ defineEarlyCutOffNoFile f = defineEarlyCutoff $ RuleNoDiagnostics $ \ k file -> do
178+ if file == emptyFilePath then do (hash, res) <- f k; return (Just hash, Just res) else
179179 fail $ " Rule " ++ show k ++ " should always be called with the empty string for a file"
180180
181181------------------------------------------------------------
@@ -308,7 +308,7 @@ priorityFilesOfInterest = Priority (-2)
308308-- and https://github.com/mpickering/ghcide/pull/22#issuecomment-625070490
309309-- GHC wiki about: https://gitlab.haskell.org/ghc/ghc/-/wikis/api-annotations
310310getParsedModuleRule :: Rules ()
311- getParsedModuleRule = defineEarlyCutoff $ \ GetParsedModule file -> do
311+ getParsedModuleRule = defineEarlyCutoff $ Rule $ \ GetParsedModule file -> do
312312 ModSummaryResult {msrModSummary = ms} <- use_ GetModSummary file
313313 sess <- use_ GhcSession file
314314 let hsc = hscEnv sess
@@ -372,8 +372,9 @@ mergeParseErrorsHaddock normal haddock = normal ++
372372-- | This rule provides a ParsedModule preserving all annotations,
373373-- including keywords, punctuation and comments.
374374-- So it is suitable for use cases where you need a perfect edit.
375+ -- FIXME this rule should probably not produce diagnostics
375376getParsedModuleWithCommentsRule :: Rules ()
376- getParsedModuleWithCommentsRule = defineEarlyCutoff $ \ GetParsedModuleWithComments file -> do
377+ getParsedModuleWithCommentsRule = defineEarlyCutoff $ Rule $ \ GetParsedModuleWithComments file -> do
377378 ModSummaryResult {msrModSummary = ms} <- use_ GetModSummary file
378379 sess <- use_ GhcSession file
379380 opt <- getIdeOptions
@@ -569,13 +570,13 @@ reportImportCyclesRule =
569570-- NOTE: result does not include the argument file.
570571getDependenciesRule :: Rules ()
571572getDependenciesRule =
572- defineEarlyCutoff $ \ GetDependencies file -> do
573+ defineEarlyCutoff $ RuleNoDiagnostics $ \ GetDependencies file -> do
573574 depInfo <- use_ GetDependencyInformation file
574575 let allFiles = reachableModules depInfo
575576 _ <- uses_ ReportImportCycles allFiles
576577 opts <- getIdeOptions
577578 let mbFingerprints = map (fingerprintString . fromNormalizedFilePath) allFiles <$ optShakeFiles opts
578- return (fingerprintToBS . fingerprintFingerprints <$> mbFingerprints, ( [] , transitiveDeps depInfo file) )
579+ return (fingerprintToBS . fingerprintFingerprints <$> mbFingerprints, transitiveDeps depInfo file)
579580
580581getHieAstsRule :: Rules ()
581582getHieAstsRule =
@@ -739,7 +740,7 @@ loadGhcSession = do
739740 let fingerprint = hash (sessionVersion res)
740741 return (BS. pack (show fingerprint), res)
741742
742- defineEarlyCutoff $ \ GhcSession file -> do
743+ defineEarlyCutoff $ Rule $ \ GhcSession file -> do
743744 IdeGhcSession {loadSessionFun} <- useNoFile_ GhcSessionIO
744745 (val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file
745746
@@ -790,7 +791,7 @@ ghcSessionDepsDefinition file = do
790791-- | Load a iface from disk, or generate it if there isn't one or it is out of date
791792-- This rule also ensures that the `.hie` and `.o` (if needed) files are written out.
792793getModIfaceFromDiskRule :: Rules ()
793- getModIfaceFromDiskRule = defineEarlyCutoff $ \ GetModIfaceFromDisk f -> do
794+ getModIfaceFromDiskRule = defineEarlyCutoff $ Rule $ \ GetModIfaceFromDisk f -> do
794795 ms <- msrModSummary <$> use_ GetModSummary f
795796 (diags_session, mb_session) <- ghcSessionDepsDefinition f
796797 case mb_session of
@@ -814,7 +815,7 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
814815-- disk since we are careful to write out the `.hie` file before writing the
815816-- `.hi` file
816817getModIfaceFromDiskAndIndexRule :: Rules ()
817- getModIfaceFromDiskAndIndexRule = defineEarlyCutoff $ \ GetModIfaceFromDiskAndIndex f -> do
818+ getModIfaceFromDiskAndIndexRule = defineEarlyCutoff $ RuleNoDiagnostics $ \ GetModIfaceFromDiskAndIndex f -> do
818819 x <- use_ GetModIfaceFromDisk f
819820 se@ ShakeExtras {hiedb} <- getShakeExtras
820821
@@ -844,10 +845,10 @@ getModIfaceFromDiskAndIndexRule = defineEarlyCutoff $ \GetModIfaceFromDiskAndInd
844845 indexHieFile se ms f hash hf
845846
846847 let fp = hiFileFingerPrint x
847- return (Just fp, ( [] , Just x) )
848+ return (Just fp, Just x)
848849
849850isHiFileStableRule :: Rules ()
850- isHiFileStableRule = defineEarlyCutoff $ \ IsHiFileStable f -> do
851+ isHiFileStableRule = defineEarlyCutoff $ RuleNoDiagnostics $ \ IsHiFileStable f -> do
851852 ms <- msrModSummary <$> use_ GetModSummaryWithoutTimestamps f
852853 let hiFile = toNormalizedFilePath'
853854 $ ml_hi_file $ ms_location ms
@@ -865,11 +866,11 @@ isHiFileStableRule = defineEarlyCutoff $ \IsHiFileStable f -> do
865866 pure $ if all (== SourceUnmodifiedAndStable ) deps
866867 then SourceUnmodifiedAndStable
867868 else SourceUnmodified
868- return (Just (BS. pack $ show sourceModified), ( [] , Just sourceModified) )
869+ return (Just (BS. pack $ show sourceModified), Just sourceModified)
869870
870871getModSummaryRule :: Rules ()
871872getModSummaryRule = do
872- defineEarlyCutoff $ \ GetModSummary f -> do
873+ defineEarlyCutoff $ Rule $ \ GetModSummary f -> do
873874 session <- hscEnv <$> use_ GhcSession f
874875 (modTime, mFileContent) <- getFileContents f
875876 let fp = fromNormalizedFilePath f
@@ -884,7 +885,7 @@ getModSummaryRule = do
884885 return ( Just (fingerprintToBS fingerPrint) , ([] , Just res))
885886 Left diags -> return (Nothing , (diags, Nothing ))
886887
887- defineEarlyCutoff $ \ GetModSummaryWithoutTimestamps f -> do
888+ defineEarlyCutoff $ RuleNoDiagnostics $ \ GetModSummaryWithoutTimestamps f -> do
888889 ms <- use GetModSummary f
889890 case ms of
890891 Just res@ ModSummaryResult {.. } -> do
@@ -893,8 +894,8 @@ getModSummaryRule = do
893894 ms_hspp_buf = error " use GetModSummary instead of GetModSummaryWithoutTimestamps"
894895 }
895896 fp = fingerprintToBS msrFingerprint
896- return (Just fp, ( [] , Just res{msrModSummary = ms}) )
897- Nothing -> return (Nothing , ( [] , Nothing ) )
897+ return (Just fp, Just res{msrModSummary = ms})
898+ Nothing -> return (Nothing , Nothing )
898899
899900generateCore :: RunSimplifier -> NormalizedFilePath -> Action (IdeResult ModGuts )
900901generateCore runSimplifier file = do
@@ -908,7 +909,7 @@ generateCoreRule =
908909 define $ \ GenerateCore -> generateCore (RunSimplifier True )
909910
910911getModIfaceRule :: Rules ()
911- getModIfaceRule = defineEarlyCutoff $ \ GetModIface f -> do
912+ getModIfaceRule = defineEarlyCutoff $ Rule $ \ GetModIface f -> do
912913 fileOfInterest <- use_ IsFileOfInterest f
913914 res@ (_,(_,mhmi)) <- case fileOfInterest of
914915 IsFOI status -> do
@@ -937,11 +938,11 @@ getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
937938 pure res
938939
939940getModIfaceWithoutLinkableRule :: Rules ()
940- getModIfaceWithoutLinkableRule = defineEarlyCutoff $ \ GetModIfaceWithoutLinkable f -> do
941+ getModIfaceWithoutLinkableRule = defineEarlyCutoff $ RuleNoDiagnostics $ \ GetModIfaceWithoutLinkable f -> do
941942 mhfr <- use GetModIface f
942943 let mhfr' = fmap (\ x -> x{ hirHomeMod = (hirHomeMod x){ hm_linkable = Just (error msg) } }) mhfr
943944 msg = " tried to look at linkable for GetModIfaceWithoutLinkable for " ++ show f
944- pure (fingerprintToBS . getModuleHash . hirModIface <$> mhfr', ( [] , mhfr') )
945+ pure (fingerprintToBS . getModuleHash . hirModIface <$> mhfr', mhfr')
945946
946947-- | Also generates and indexes the `.hie` file, along with the `.o` file if needed
947948-- Invariant maintained is that if the `.hi` file was successfully written, then the
@@ -1037,7 +1038,7 @@ getLinkableType :: NormalizedFilePath -> Action (Maybe LinkableType)
10371038getLinkableType f = use_ NeedsCompilation f
10381039
10391040needsCompilationRule :: Rules ()
1040- needsCompilationRule = defineEarlyCutoff $ \ NeedsCompilation file -> do
1041+ needsCompilationRule = defineEarlyCutoff $ RuleNoDiagnostics $ \ NeedsCompilation file -> do
10411042 graph <- useNoFile GetModuleGraph
10421043 res <- case graph of
10431044 -- Treat as False if some reverse dependency header fails to parse
@@ -1061,7 +1062,7 @@ needsCompilationRule = defineEarlyCutoff $ \NeedsCompilation file -> do
10611062 (uses NeedsCompilation revdeps)
10621063 pure $ computeLinkableType ms modsums (map join needsComps)
10631064
1064- pure (Just $ BS. pack $ show $ hash res, ( [] , Just res) )
1065+ pure (Just $ BS. pack $ show $ hash res, Just res)
10651066 where
10661067 uses_th_qq (ms_hspp_opts -> dflags) =
10671068 xopt LangExt. TemplateHaskell dflags || xopt LangExt. QuasiQuotes dflags
0 commit comments