@@ -67,7 +67,6 @@ import Data.Proxy (Proxy (Proxy))
67
67
import qualified Data.Text as T
68
68
import Data.Time (UTCTime (.. ))
69
69
import Data.Tuple.Extra (dupe )
70
- import Data.Unique as Unique
71
70
import Debug.Trace
72
71
import Development.IDE.Core.FileStore (resetInterfaceStore )
73
72
import Development.IDE.Core.Preprocessor
@@ -81,6 +80,7 @@ import Development.IDE.GHC.Compat hiding (assert,
81
80
import qualified Development.IDE.GHC.Compat as Compat
82
81
import qualified Development.IDE.GHC.Compat as GHC
83
82
import qualified Development.IDE.GHC.Compat.Util as Util
83
+ import Development.IDE.Core.ProgressReporting (ProgressReporting (.. ), progressReportingOutsideState )
84
84
import Development.IDE.GHC.CoreFile
85
85
import Development.IDE.GHC.Error
86
86
import Development.IDE.GHC.Orphans ()
@@ -97,7 +97,6 @@ import GHC.Serialized
97
97
import HieDb hiding (withHieDb )
98
98
import qualified Language.LSP.Protocol.Message as LSP
99
99
import Language.LSP.Protocol.Types (DiagnosticTag (.. ))
100
- import qualified Language.LSP.Protocol.Types as LSP
101
100
import qualified Language.LSP.Server as LSP
102
101
import Prelude hiding (mod )
103
102
import System.Directory
@@ -785,7 +784,6 @@ spliceExpressions Splices{..} =
785
784
--
786
785
indexHieFile :: ShakeExtras -> ModSummary -> NormalizedFilePath -> Util. Fingerprint -> Compat. HieFile -> IO ()
787
786
indexHieFile se mod_summary srcPath ! hash hf = do
788
- IdeOptions {optProgressStyle} <- getIdeOptionsIO se
789
787
atomically $ do
790
788
pending <- readTVar indexPending
791
789
case HashMap. lookup srcPath pending of
@@ -806,69 +804,14 @@ indexHieFile se mod_summary srcPath !hash hf = do
806
804
unless newerScheduled $ do
807
805
-- Using bracket, so even if an exception happen during withHieDb call,
808
806
-- the `post` (which clean the progress indicator) will still be called.
809
- bracket_ ( pre optProgressStyle) post $
807
+ bracket_ pre post $
810
808
withHieDb (\ db -> HieDb. addRefsFromLoaded db targetPath (HieDb. RealFile $ fromNormalizedFilePath srcPath) hash hf')
811
809
where
812
810
mod_location = ms_location mod_summary
813
811
targetPath = Compat. ml_hie_file mod_location
814
812
HieDbWriter {.. } = hiedbWriter se
815
813
816
- -- Get a progress token to report progress and update it for the current file
817
- pre style = do
818
- tok <- modifyVar indexProgressToken $ fmap dupe . \ case
819
- x@ (Just _) -> pure x
820
- -- Create a token if we don't already have one
821
- Nothing -> do
822
- case lspEnv se of
823
- Nothing -> pure Nothing
824
- Just env -> LSP. runLspT env $ do
825
- u <- LSP. ProgressToken . LSP. InR . T. pack . show . hashUnique <$> liftIO Unique. newUnique
826
- -- TODO: Wait for the progress create response to use the token
827
- _ <- LSP. sendRequest LSP. SMethod_WindowWorkDoneProgressCreate (LSP. WorkDoneProgressCreateParams u) (const $ pure () )
828
- LSP. sendNotification LSP. SMethod_Progress $ LSP. ProgressParams u $
829
- toJSON $ LSP. WorkDoneProgressBegin
830
- { _kind = LSP. AString @ " begin"
831
- , _title = " Indexing"
832
- , _cancellable = Nothing
833
- , _message = Nothing
834
- , _percentage = Nothing
835
- }
836
- pure (Just u)
837
-
838
- (! done, ! remaining) <- atomically $ do
839
- done <- readTVar indexCompleted
840
- remaining <- HashMap. size <$> readTVar indexPending
841
- pure (done, remaining)
842
- let
843
- progressFrac :: Double
844
- progressFrac = fromIntegral done / fromIntegral (done + remaining)
845
- progressPct :: LSP. UInt
846
- progressPct = floor $ 100 * progressFrac
847
-
848
- whenJust (lspEnv se) $ \ env -> whenJust tok $ \ token -> LSP. runLspT env $
849
- LSP. sendNotification LSP. SMethod_Progress $ LSP. ProgressParams token $
850
- toJSON $
851
- case style of
852
- Percentage -> LSP. WorkDoneProgressReport
853
- { _kind = LSP. AString @ " report"
854
- , _cancellable = Nothing
855
- , _message = Nothing
856
- , _percentage = Just progressPct
857
- }
858
- Explicit -> LSP. WorkDoneProgressReport
859
- { _kind = LSP. AString @ " report"
860
- , _cancellable = Nothing
861
- , _message = Just $
862
- T. pack " (" <> T. pack (show done) <> " /" <> T. pack (show $ done + remaining) <> " )..."
863
- , _percentage = Nothing
864
- }
865
- NoProgress -> LSP. WorkDoneProgressReport
866
- { _kind = LSP. AString @ " report"
867
- , _cancellable = Nothing
868
- , _message = Nothing
869
- , _percentage = Nothing
870
- }
871
-
814
+ pre = progressUpdate indexProgressReporting ProgressStarted
872
815
-- Report the progress once we are done indexing this file
873
816
post = do
874
817
mdone <- atomically $ do
@@ -883,18 +826,7 @@ indexHieFile se mod_summary srcPath !hash hf = do
883
826
when (coerce $ ideTesting se) $
884
827
LSP. sendNotification (LSP. SMethod_CustomMethod (Proxy @ " ghcide/reference/ready" )) $
885
828
toJSON $ fromNormalizedFilePath srcPath
886
- whenJust mdone $ \ done ->
887
- modifyVar_ indexProgressToken $ \ tok -> do
888
- whenJust (lspEnv se) $ \ env -> LSP. runLspT env $
889
- whenJust tok $ \ token ->
890
- LSP. sendNotification LSP. SMethod_Progress $ LSP. ProgressParams token $
891
- toJSON $
892
- LSP. WorkDoneProgressEnd
893
- { _kind = LSP. AString @ " end"
894
- , _message = Just $ " Finished indexing " <> T. pack (show done) <> " files"
895
- }
896
- -- We are done with the current indexing cycle, so destroy the token
897
- pure Nothing
829
+ whenJust mdone $ \ _ -> progressUpdate indexProgressReporting ProgressCompleted
898
830
899
831
writeAndIndexHieFile :: HscEnv -> ShakeExtras -> ModSummary -> NormalizedFilePath -> [GHC. AvailInfo ] -> HieASTs Type -> BS. ByteString -> IO [FileDiagnostic ]
900
832
writeAndIndexHieFile hscEnv se mod_summary srcPath exports ast source =
0 commit comments