@@ -77,6 +77,8 @@ import Data.Map.Strict (Map)
7777import Data.List.Extra (partition , takeEnd )
7878import qualified Data.Set as Set
7979import qualified Data.Text as T
80+ import Data.Vector (Vector )
81+ import qualified Data.Vector as Vector
8082import Data.Tuple.Extra
8183import Data.Unique
8284import Development.IDE.Core.Debouncer
@@ -313,10 +315,11 @@ setValues :: IdeRule k v
313315 -> k
314316 -> NormalizedFilePath
315317 -> Value v
318+ -> Vector FileDiagnostic
316319 -> IO ()
317- setValues state key file val = modifyVar_ state $ \ vals -> do
320+ setValues state key file val diags = modifyVar_ state $ \ vals -> do
318321 -- 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
320323
321324-- | Delete the value stored for a given ide build key
322325deleteValue
@@ -329,17 +332,23 @@ deleteValue IdeState{shakeExtras = ShakeExtras{state}} key file = modifyVar_ sta
329332 evaluate $ HMap. delete (file, Key key) vals
330333
331334-- | 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 ))
333342getValues state key file = do
334343 vs <- readVar state
335344 case HMap. lookup (file, Key key) vs of
336345 Nothing -> pure Nothing
337- Just v -> do
346+ Just ( ValueWithDiagnostics v diagsV) -> do
338347 let r = fmap (fromJust . fromDynamic @ v ) v
339348 -- Force to make sure we do not retain a reference to the HashMap
340349 -- and we blow up immediately if the fromJust should fail
341350 -- (which would be an internal error).
342- evaluate (r `seqValue` Just r )
351+ evaluate (r `seqValue` Just (r, diagsV) )
343352
344353-- | Get all the files in the project
345354knownTargets :: Action (Hashed KnownTargets )
@@ -663,7 +672,7 @@ garbageCollect keep = do
663672 modifyVar_ publishedDiagnostics $ \ diags -> return $! HMap. filterWithKey (\ uri _ -> keep (fromUri uri)) diags
664673 let versionsForFile =
665674 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) $
667676 HMap. toList newState
668677 modifyVar_ positionMapping $ \ mappings -> return $! filterVersionMap versionsForFile mappings
669678
@@ -743,11 +752,11 @@ useWithStaleFast' key file = do
743752 r <- getValues state key file
744753 case r of
745754 Nothing -> return $ FastResult Nothing (pure a)
746- Just v -> do
755+ Just (v, _) -> do
747756 res <- lastValueIO s file v
748757 pure $ FastResult res (pure a)
749758 -- Otherwise, use the computed value even if it's out of date.
750- Just v -> do
759+ Just (v, _) -> do
751760 res <- lastValueIO s file v
752761 pure $ FastResult res wait
753762
@@ -767,45 +776,6 @@ uses_ key files = do
767776 Nothing -> liftIO $ throwIO $ BadDependency (show key)
768777 Just v -> return v
769778
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-
809779-- | Plural version of 'use'
810780uses :: IdeRule k v
811781 => k -> [NormalizedFilePath ] -> Action [Maybe v ]
@@ -833,7 +803,9 @@ defineEarlyCutoff op = addBuiltinRule noLint noIdentity $ \(Q (key, file)) (old
833803 case v of
834804 -- No changes in the dependencies and we have
835805 -- 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
837809 _ -> return Nothing
838810 _ -> return Nothing
839811 case val of
@@ -842,18 +814,21 @@ defineEarlyCutoff op = addBuiltinRule noLint noIdentity $ \(Q (key, file)) (old
842814 (bs, (diags, res)) <- actionCatch
843815 (do v <- op key file; liftIO $ evaluate $ force v) $
844816 \ (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
847819 Nothing -> do
848820 staleV <- liftIO $ getValues state key file
849821 pure $ case staleV of
850- Nothing -> (toShakeValue ShakeResult bs, Failed )
822+ Nothing -> (toShakeValue ShakeResult bs, diags, Vector. fromList diags, Failed )
851823 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
857832 updateFileDiagnostics file (Key key) extras $ map (\ (_,y,z) -> (y,z)) diags
858833 let eq = case (bs, fmap decodeShakeValue old) of
859834 (ShakeResult a, Just (ShakeResult b)) -> a == b
@@ -952,44 +927,14 @@ needOnDisks k files = do
952927 successfulls <- apply $ map (QDisk k) files
953928 liftIO $ unless (and successfulls) $ throwIO $ BadDependency (show k)
954929
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-
985930updateFileDiagnostics :: MonadIO m
986931 => NormalizedFilePath
987932 -> Key
988933 -> ShakeExtras
989934 -> [(ShowDiagnostic ,Diagnostic )] -- ^ current results
990935 -> m ()
991936updateFileDiagnostics 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
993938 let (currentShown, currentHidden) = partition ((== ShowDiag ) . fst ) current
994939 uri = filePathToUri' fp
995940 ver = vfsVersion =<< modTime
@@ -1051,18 +996,9 @@ setStageDiagnostics
1051996 -> [LSP. Diagnostic ]
1052997 -> DiagnosticStore
1053998 -> 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)
10661002
10671003getAllDiagnostics ::
10681004 DiagnosticStore ->
0 commit comments