@@ -77,6 +77,8 @@ import Data.Map.Strict (Map)
77
77
import Data.List.Extra (partition , takeEnd )
78
78
import qualified Data.Set as Set
79
79
import qualified Data.Text as T
80
+ import Data.Vector (Vector )
81
+ import qualified Data.Vector as Vector
80
82
import Data.Tuple.Extra
81
83
import Data.Unique
82
84
import Development.IDE.Core.Debouncer
@@ -313,10 +315,11 @@ setValues :: IdeRule k v
313
315
-> k
314
316
-> NormalizedFilePath
315
317
-> Value v
318
+ -> Vector FileDiagnostic
316
319
-> IO ()
317
- setValues state key file val = modifyVar_ state $ \ vals -> do
320
+ setValues state key file val diags = modifyVar_ state $ \ vals -> do
318
321
-- Force to make sure the old HashMap is not retained
319
- evaluate $ HMap. insert (file, Key key) (fmap toDyn val) vals
322
+ evaluate $ HMap. insert (file, Key key) (ValueWithDiagnostics ( fmap toDyn val) diags ) vals
320
323
321
324
-- | Delete the value stored for a given ide build key
322
325
deleteValue
@@ -329,17 +332,23 @@ deleteValue IdeState{shakeExtras = ShakeExtras{state}} key file = modifyVar_ sta
329
332
evaluate $ HMap. delete (file, Key key) vals
330
333
331
334
-- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value.
332
- getValues :: forall k v . IdeRule k v => Var Values -> k -> NormalizedFilePath -> IO (Maybe (Value v ))
335
+ getValues ::
336
+ forall k v .
337
+ IdeRule k v =>
338
+ Var Values ->
339
+ k ->
340
+ NormalizedFilePath ->
341
+ IO (Maybe (Value v , Vector FileDiagnostic ))
333
342
getValues state key file = do
334
343
vs <- readVar state
335
344
case HMap. lookup (file, Key key) vs of
336
345
Nothing -> pure Nothing
337
- Just v -> do
346
+ Just ( ValueWithDiagnostics v diagsV) -> do
338
347
let r = fmap (fromJust . fromDynamic @ v ) v
339
348
-- Force to make sure we do not retain a reference to the HashMap
340
349
-- and we blow up immediately if the fromJust should fail
341
350
-- (which would be an internal error).
342
- evaluate (r `seqValue` Just r )
351
+ evaluate (r `seqValue` Just (r, diagsV) )
343
352
344
353
-- | Get all the files in the project
345
354
knownTargets :: Action (Hashed KnownTargets )
@@ -663,7 +672,7 @@ garbageCollect keep = do
663
672
modifyVar_ publishedDiagnostics $ \ diags -> return $! HMap. filterWithKey (\ uri _ -> keep (fromUri uri)) diags
664
673
let versionsForFile =
665
674
HMap. fromListWith Set. union $
666
- mapMaybe (\ ((file, _key), v ) -> (filePathToUri' file,) . Set. singleton <$> valueVersion v) $
675
+ mapMaybe (\ ((file, _key), ValueWithDiagnostics v _ ) -> (filePathToUri' file,) . Set. singleton <$> valueVersion v) $
667
676
HMap. toList newState
668
677
modifyVar_ positionMapping $ \ mappings -> return $! filterVersionMap versionsForFile mappings
669
678
@@ -743,11 +752,11 @@ useWithStaleFast' key file = do
743
752
r <- getValues state key file
744
753
case r of
745
754
Nothing -> return $ FastResult Nothing (pure a)
746
- Just v -> do
755
+ Just (v, _) -> do
747
756
res <- lastValueIO s file v
748
757
pure $ FastResult res (pure a)
749
758
-- Otherwise, use the computed value even if it's out of date.
750
- Just v -> do
759
+ Just (v, _) -> do
751
760
res <- lastValueIO s file v
752
761
pure $ FastResult res wait
753
762
@@ -767,45 +776,6 @@ uses_ key files = do
767
776
Nothing -> liftIO $ throwIO $ BadDependency (show key)
768
777
Just v -> return v
769
778
770
-
771
- -- | When we depend on something that reported an error, and we fail as a direct result, throw BadDependency
772
- -- which short-circuits the rest of the action
773
- data BadDependency = BadDependency String deriving Show
774
- instance Exception BadDependency
775
-
776
- isBadDependency :: SomeException -> Bool
777
- isBadDependency x
778
- | Just (x :: ShakeException ) <- fromException x = isBadDependency $ shakeExceptionInner x
779
- | Just (_ :: BadDependency ) <- fromException x = True
780
- | otherwise = False
781
-
782
- newtype Q k = Q (k , NormalizedFilePath )
783
- deriving newtype (Eq , Hashable , NFData )
784
-
785
- instance Binary k => Binary (Q k ) where
786
- put (Q (k, fp)) = put (k, fp)
787
- get = do
788
- (k, fp) <- get
789
- -- The `get` implementation of NormalizedFilePath
790
- -- does not handle empty file paths so we
791
- -- need to handle this ourselves here.
792
- pure (Q (k, toNormalizedFilePath' fp))
793
-
794
- instance Show k => Show (Q k ) where
795
- show (Q (k, file)) = show k ++ " ; " ++ fromNormalizedFilePath file
796
-
797
- -- | Invariant: the 'v' must be in normal form (fully evaluated).
798
- -- Otherwise we keep repeatedly 'rnf'ing values taken from the Shake database
799
- newtype A v = A (Value v )
800
- deriving Show
801
-
802
- instance NFData (A v ) where rnf (A v) = v `seq` ()
803
-
804
- -- In the Shake database we only store one type of key/result pairs,
805
- -- namely Q (question) / A (answer).
806
- type instance RuleResult (Q k ) = A (RuleResult k )
807
-
808
-
809
779
-- | Plural version of 'use'
810
780
uses :: IdeRule k v
811
781
=> k -> [NormalizedFilePath ] -> Action [Maybe v ]
@@ -833,7 +803,9 @@ defineEarlyCutoff op = addBuiltinRule noLint noIdentity $ \(Q (key, file)) (old
833
803
case v of
834
804
-- No changes in the dependencies and we have
835
805
-- an existing result.
836
- Just v -> return $ Just $ RunResult ChangedNothing old $ A v
806
+ Just (v, diags) -> do
807
+ updateFileDiagnostics file (Key key) extras $ map (\ (_,y,z) -> (y,z)) $ Vector. toList diags
808
+ return $ Just $ RunResult ChangedNothing old $ A v
837
809
_ -> return Nothing
838
810
_ -> return Nothing
839
811
case val of
@@ -842,18 +814,21 @@ defineEarlyCutoff op = addBuiltinRule noLint noIdentity $ \(Q (key, file)) (old
842
814
(bs, (diags, res)) <- actionCatch
843
815
(do v <- op key file; liftIO $ evaluate $ force v) $
844
816
\ (e :: SomeException ) -> pure (Nothing , ([ideErrorText file $ T. pack $ show e | not $ isBadDependency e],Nothing ))
845
- modTime <- liftIO $ (currentValue =<< ) <$> getValues state GetModificationTime file
846
- (bs, res) <- case res of
817
+ modTime <- liftIO $ (currentValue . fst =<< ) <$> getValues state GetModificationTime file
818
+ (bs, diags, diagsV, res) <- case res of
847
819
Nothing -> do
848
820
staleV <- liftIO $ getValues state key file
849
821
pure $ case staleV of
850
- Nothing -> (toShakeValue ShakeResult bs, Failed )
822
+ Nothing -> (toShakeValue ShakeResult bs, diags, Vector. fromList diags, Failed )
851
823
Just v -> case v of
852
- Succeeded ver v -> (toShakeValue ShakeStale bs, Stale ver v)
853
- Stale ver v -> (toShakeValue ShakeStale bs, Stale ver v)
854
- Failed -> (toShakeValue ShakeResult bs, Failed )
855
- Just v -> pure (maybe ShakeNoCutoff ShakeResult bs, Succeeded (vfsVersion =<< modTime) v)
856
- liftIO $ setValues state key file res
824
+ (Succeeded ver v, diags) ->
825
+ (toShakeValue ShakeStale bs, Vector. toList diags, diags, Stale ver v)
826
+ (Stale ver v, diags) ->
827
+ (toShakeValue ShakeStale bs, Vector. toList diags, diags, Stale ver v)
828
+ (Failed , diags) ->
829
+ (toShakeValue ShakeResult bs, Vector. toList diags, diags, Failed )
830
+ Just v -> pure (maybe ShakeNoCutoff ShakeResult bs, diags, Vector. fromList diags, Succeeded (vfsVersion =<< modTime) v)
831
+ liftIO $ setValues state key file res diagsV
857
832
updateFileDiagnostics file (Key key) extras $ map (\ (_,y,z) -> (y,z)) diags
858
833
let eq = case (bs, fmap decodeShakeValue old) of
859
834
(ShakeResult a, Just (ShakeResult b)) -> a == b
@@ -952,44 +927,14 @@ needOnDisks k files = do
952
927
successfulls <- apply $ map (QDisk k) files
953
928
liftIO $ unless (and successfulls) $ throwIO $ BadDependency (show k)
954
929
955
- toShakeValue :: (BS. ByteString -> ShakeValue ) -> Maybe BS. ByteString -> ShakeValue
956
- toShakeValue = maybe ShakeNoCutoff
957
-
958
- data ShakeValue
959
- = ShakeNoCutoff
960
- -- ^ This is what we use when we get Nothing from
961
- -- a rule.
962
- | ShakeResult ! BS. ByteString
963
- -- ^ This is used both for `Failed`
964
- -- as well as `Succeeded`.
965
- | ShakeStale ! BS. ByteString
966
- deriving (Generic , Show )
967
-
968
- instance NFData ShakeValue
969
-
970
- encodeShakeValue :: ShakeValue -> BS. ByteString
971
- encodeShakeValue = \ case
972
- ShakeNoCutoff -> BS. empty
973
- ShakeResult r -> BS. cons ' r' r
974
- ShakeStale r -> BS. cons ' s' r
975
-
976
- decodeShakeValue :: BS. ByteString -> ShakeValue
977
- decodeShakeValue bs = case BS. uncons bs of
978
- Nothing -> ShakeNoCutoff
979
- Just (x, xs)
980
- | x == ' r' -> ShakeResult xs
981
- | x == ' s' -> ShakeStale xs
982
- | otherwise -> error $ " Failed to parse shake value " <> show bs
983
-
984
-
985
930
updateFileDiagnostics :: MonadIO m
986
931
=> NormalizedFilePath
987
932
-> Key
988
933
-> ShakeExtras
989
934
-> [(ShowDiagnostic ,Diagnostic )] -- ^ current results
990
935
-> m ()
991
936
updateFileDiagnostics fp k ShakeExtras {diagnostics, hiddenDiagnostics, publishedDiagnostics, state, debouncer, eventer} current = liftIO $ do
992
- modTime <- (currentValue =<< ) <$> getValues state GetModificationTime fp
937
+ modTime <- (currentValue . fst =<< ) <$> getValues state GetModificationTime fp
993
938
let (currentShown, currentHidden) = partition ((== ShowDiag ) . fst ) current
994
939
uri = filePathToUri' fp
995
940
ver = vfsVersion =<< modTime
@@ -1051,18 +996,9 @@ setStageDiagnostics
1051
996
-> [LSP. Diagnostic ]
1052
997
-> DiagnosticStore
1053
998
-> DiagnosticStore
1054
- setStageDiagnostics uri ver stage diags ds = newDiagsStore where
1055
- -- When 'ver' is a new version, updateDiagnostics throws away diagnostics from all stages
1056
- -- This interacts bady with early cutoff, so we make sure to preserve diagnostics
1057
- -- from other stages when calling updateDiagnostics
1058
- -- But this means that updateDiagnostics cannot be called concurrently
1059
- -- for different stages anymore
1060
- updatedDiags = Map. insert (Just stage) (SL. toSortedList diags) oldDiags
1061
- oldDiags = case HMap. lookup uri ds of
1062
- Just (StoreItem _ byStage) -> byStage
1063
- _ -> Map. empty
1064
- newDiagsStore = updateDiagnostics ds uri ver updatedDiags
1065
-
999
+ setStageDiagnostics uri ver stage diags ds = updateDiagnostics ds uri ver updatedDiags
1000
+ where
1001
+ updatedDiags = Map. singleton (Just stage) (SL. toSortedList diags)
1066
1002
1067
1003
getAllDiagnostics ::
1068
1004
DiagnosticStore ->
0 commit comments