Skip to content

Commit 82148dc

Browse files
authored
Fix hls-graph: phantom dependencies invoke in branching deps (resolve #3423) (#4087)
phantom depencies is invoke becase dependencies have preconditions in rules, see #3423. This pr is intend to fix that. This might also fix some of the flaky tests. In favor of @wz1000 appoach of running deps linearly. It modify the deps result from KeySet to [KeySet] to make sure the result is sorted we initialy thought it would have performance impact on the build system. But it turns out instead of performance lost, we actaully have performance gain since it avoid building the phantom depencies. Overall things have been done: 1. Fix up hls-graph phantom depencies issue by reflesh linear deps in a linear manner. 2. Add semantic tokens bench mark. 3. Add test to hls-graph to ensure phantom depencies would not be invoke. Result: Now no more phantom dependencies would be invoked in hls-graph, gaining correctness, less runtime and less mem usage at the some time.
1 parent 5453ab5 commit 82148dc

File tree

10 files changed

+131
-33
lines changed

10 files changed

+131
-33
lines changed

Diff for: bench/config.yaml

+2
Original file line numberDiff line numberDiff line change
@@ -94,6 +94,7 @@ experiments:
9494
- "edit-header"
9595
- "edit"
9696
- "hover"
97+
- "semanticTokens"
9798
- "hover after edit"
9899
# - "hover after cradle edit"
99100
- "getDefinition"
@@ -194,6 +195,7 @@ configurations:
194195
- qualifyImportedNames
195196
- rename
196197
- stylish-haskell
198+
- semanticTokens
197199
# - alternateNumberFormat
198200
# - callHierarchy
199201
# - changeTypeSignature

Diff for: ghcide-bench/src/Experiments.hs

+17-4
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,8 @@ import Control.Applicative.Combinators (skipManyTill)
2626
import Control.Concurrent.Async (withAsync)
2727
import Control.Exception.Safe (IOException, handleAny,
2828
try)
29-
import Control.Lens (_Just, (&), (.~), (^.))
29+
import Control.Lens (_Just, (&), (.~), (^.),
30+
(^?))
3031
import Control.Lens.Extras (is)
3132
import Control.Monad.Extra (allM, forM, forM_, forever,
3233
unless, void, when,
@@ -100,7 +101,19 @@ allWithIdentifierPos f docs = case applicableDocs of
100101

101102
experiments :: HasConfig => [Bench]
102103
experiments =
103-
[ ---------------------------------------------------------------------------------------
104+
[
105+
bench "semanticTokens" $ \docs -> do
106+
liftIO $ putStrLn "Starting semanticTokens"
107+
r <- forM docs $ \DocumentPositions{..} -> do
108+
changeDoc doc [charEdit stringLiteralP]
109+
waitForProgressStart
110+
waitForProgressDone
111+
tks <- getSemanticTokens doc
112+
case tks ^? LSP._L of
113+
Just _ -> return True
114+
Nothing -> return False
115+
return $ and r,
116+
---------------------------------------------------------------------------------------
104117
bench "hover" $ allWithIdentifierPos $ \DocumentPositions{..} ->
105118
isJust <$> getHover doc (fromJust identifierP),
106119
---------------------------------------------------------------------------------------
@@ -316,7 +329,7 @@ versionP = maybeReader $ extract . readP_to_S parseVersion
316329
extract parses = listToMaybe [ res | (res,"") <- parses]
317330

318331
output :: (MonadIO m, HasConfig) => String -> m ()
319-
output = if quiet?config then (\_ -> pure ()) else liftIO . putStrLn
332+
output = if quiet ?config then (\_ -> pure ()) else liftIO . putStrLn
320333

321334
---------------------------------------------------------------------------------------
322335

@@ -670,7 +683,7 @@ setup = do
670683

671684
whenJust (shakeProfiling ?config) $ createDirectoryIfMissing True
672685

673-
let cleanUp = case exampleDetails(example ?config) of
686+
let cleanUp = case exampleDetails (example ?config) of
674687
ExampleHackage _ -> removeDirectoryRecursive examplesPath
675688
ExampleScript _ _ -> removeDirectoryRecursive examplesPath
676689
ExamplePath _ -> return ()

Diff for: hls-graph/src/Development/IDE/Graph/Database.hs

+1
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Development.IDE.Graph.Database(
1212
,shakeGetBuildEdges) where
1313
import Control.Concurrent.STM.Stats (readTVarIO)
1414
import Data.Dynamic
15+
import Data.Foldable (fold)
1516
import Data.Maybe
1617
import Development.IDE.Graph.Classes ()
1718
import Development.IDE.Graph.Internal.Action

Diff for: hls-graph/src/Development/IDE/Graph/Internal/Action.hs

+4-2
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,7 @@ module Development.IDE.Graph.Internal.Action
1818
) where
1919

2020
import Control.Concurrent.Async
21+
import Control.DeepSeq (force)
2122
import Control.Exception
2223
import Control.Monad.IO.Class
2324
import Control.Monad.Trans.Class
@@ -38,7 +39,7 @@ type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, NFData a)
3839
alwaysRerun :: Action ()
3940
alwaysRerun = do
4041
ref <- Action $ asks actionDeps
41-
liftIO $ modifyIORef ref (AlwaysRerunDeps mempty <>)
42+
liftIO $ modifyIORef' ref (AlwaysRerunDeps mempty <>)
4243

4344
-- No-op for now
4445
reschedule :: Double -> Action ()
@@ -120,7 +121,8 @@ apply ks = do
120121
stack <- Action $ asks actionStack
121122
(is, vs) <- liftIO $ build db stack ks
122123
ref <- Action $ asks actionDeps
123-
liftIO $ modifyIORef ref (ResultDeps (fromListKeySet $ toList is) <>)
124+
let !ks = force $ fromListKeySet $ toList is
125+
liftIO $ modifyIORef' ref (ResultDeps [ks] <>)
124126
pure vs
125127

126128
-- | Evaluate a list of keys without recording any dependencies.

Diff for: hls-graph/src/Development/IDE/Graph/Internal/Database.hs

+33-18
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@
33
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
44

55
{-# LANGUAGE DerivingStrategies #-}
6+
{-# LANGUAGE LambdaCase #-}
67
{-# LANGUAGE RecordWildCards #-}
78
{-# LANGUAGE TypeFamilies #-}
8-
{-# LANGUAGE ViewPatterns #-}
99

1010
module Development.IDE.Graph.Internal.Database (newDatabase, incDatabase, build, getDirtySet, getKeysAndVisitAge) where
1111

@@ -25,7 +25,7 @@ import Control.Monad.Trans.Reader
2525
import qualified Control.Monad.Trans.State.Strict as State
2626
import Data.Dynamic
2727
import Data.Either
28-
import Data.Foldable (for_, traverse_)
28+
import Data.Foldable (fold, for_, traverse_)
2929
import Data.IORef.Extra
3030
import Data.List.NonEmpty (unzip)
3131
import Data.Maybe
@@ -133,26 +133,41 @@ builder db@Database{..} stack keys = withRunInIO $ \(RunInIO run) -> do
133133
waitAll
134134
pure results
135135

136+
isDirty :: Foldable t => Result -> t (a, Result) -> Bool
137+
isDirty me = any (\(_,dep) -> resultBuilt me < resultChanged dep)
138+
139+
-- | Refresh dependencies for a key and compute the key:
140+
-- The refresh the deps linearly(last computed order of the deps for the key).
141+
-- If any of the deps is dirty in the process, we jump to the actual computation of the key
142+
-- and shortcut the refreshing of the rest of the deps.
143+
-- * If no dirty dependencies and we have evaluated the key previously, then we refresh it in the current thread.
144+
-- This assumes that the implementation will be a lookup
145+
-- * Otherwise, we spawn a new thread to refresh the dirty deps (if any) and the key itself
146+
refreshDeps :: KeySet -> Database -> Stack -> Key -> Result -> [KeySet] -> AIO (IO Result)
147+
refreshDeps visited db stack key result = \case
148+
-- no more deps to refresh
149+
[] -> pure $ compute db stack key RunDependenciesSame (Just result)
150+
(dep:deps) -> do
151+
let newVisited = dep <> visited
152+
res <- builder db stack (toListKeySet (dep `differenceKeySet` visited))
153+
case res of
154+
Left res -> if isDirty result res
155+
-- restart the computation if any of the deps are dirty
156+
then asyncWithCleanUp $ liftIO $ compute db stack key RunDependenciesChanged (Just result)
157+
-- else kick the rest of the deps
158+
else refreshDeps newVisited db stack key result deps
159+
Right iores -> asyncWithCleanUp $ liftIO $ do
160+
res <- iores
161+
if isDirty result res
162+
then compute db stack key RunDependenciesChanged (Just result)
163+
else join $ runAIO $ refreshDeps newVisited db stack key result deps
164+
136165
-- | Refresh a key:
137-
-- * If no dirty dependencies and we have evaluated the key previously, then we refresh it in the current thread.
138-
-- This assumes that the implementation will be a lookup
139-
-- * Otherwise, we spawn a new thread to refresh the dirty deps (if any) and the key itself
140166
refresh :: Database -> Stack -> Key -> Maybe Result -> AIO (IO Result)
141167
-- refresh _ st k _ | traceShow ("refresh", st, k) False = undefined
142168
refresh db stack key result = case (addStack key stack, result) of
143169
(Left e, _) -> throw e
144-
(Right stack, Just me@Result{resultDeps = ResultDeps (toListKeySet -> deps)}) -> do
145-
res <- builder db stack deps
146-
let isDirty = any (\(_,dep) -> resultBuilt me < resultChanged dep)
147-
case res of
148-
Left res ->
149-
if isDirty res
150-
then asyncWithCleanUp $ liftIO $ compute db stack key RunDependenciesChanged result
151-
else pure $ compute db stack key RunDependenciesSame result
152-
Right iores -> asyncWithCleanUp $ liftIO $ do
153-
res <- iores
154-
let mode = if isDirty res then RunDependenciesChanged else RunDependenciesSame
155-
compute db stack key mode result
170+
(Right stack, Just me@Result{resultDeps = ResultDeps deps}) -> refreshDeps mempty db stack key me (reverse deps)
156171
(Right stack, _) ->
157172
asyncWithCleanUp $ liftIO $ compute db stack key RunDependenciesChanged result
158173

@@ -173,7 +188,7 @@ compute db@Database{..} stack key mode result = do
173188
previousDeps= maybe UnknownDeps resultDeps result
174189
let res = Result runValue built' changed built actualDeps execution runStore
175190
case getResultDepsDefault mempty actualDeps of
176-
deps | not(nullKeySet deps)
191+
deps | not (nullKeySet deps)
177192
&& runChanged /= ChangedNothing
178193
-> do
179194
-- IMPORTANT: record the reverse deps **before** marking the key Clean.

Diff for: hls-graph/src/Development/IDE/Graph/Internal/Key.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ renderKey :: Key -> Text
101101
renderKey (lookupKeyValue -> KeyValue _ t) = t
102102

103103
newtype KeySet = KeySet IntSet
104-
deriving newtype (Eq, Ord, Semigroup, Monoid)
104+
deriving newtype (Eq, Ord, Semigroup, Monoid, NFData)
105105

106106
instance Show KeySet where
107107
showsPrec p (KeySet is)= showParen (p > 10) $

Diff for: hls-graph/src/Development/IDE/Graph/Internal/Profile.hs

+1
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Data.Bifunctor
1212
import qualified Data.ByteString.Lazy.Char8 as LBS
1313
import Data.Char
1414
import Data.Dynamic (toDyn)
15+
import Data.Foldable (fold)
1516
import qualified Data.HashMap.Strict as Map
1617
import Data.List (dropWhileEnd, foldl',
1718
intercalate,

Diff for: hls-graph/src/Development/IDE/Graph/Internal/Types.hs

+8-3
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ import Data.Aeson (FromJSON, ToJSON)
1212
import Data.Bifunctor (second)
1313
import qualified Data.ByteString as BS
1414
import Data.Dynamic
15+
import Data.Foldable (fold)
1516
import qualified Data.HashMap.Strict as Map
1617
import Data.IORef
1718
import Data.List (intercalate)
@@ -144,16 +145,20 @@ data Result = Result {
144145
resultData :: !BS.ByteString
145146
}
146147

147-
data ResultDeps = UnknownDeps | AlwaysRerunDeps !KeySet | ResultDeps !KeySet
148+
-- Notice, invariant to maintain:
149+
-- the ![KeySet] in ResultDeps need to be stored in reverse order,
150+
-- so that we can append to it efficiently, and we need the ordering
151+
-- so we can do a linear dependency refreshing in refreshDeps.
152+
data ResultDeps = UnknownDeps | AlwaysRerunDeps !KeySet | ResultDeps ![KeySet]
148153
deriving (Eq, Show)
149154

150155
getResultDepsDefault :: KeySet -> ResultDeps -> KeySet
151-
getResultDepsDefault _ (ResultDeps ids) = ids
156+
getResultDepsDefault _ (ResultDeps ids) = fold ids
152157
getResultDepsDefault _ (AlwaysRerunDeps ids) = ids
153158
getResultDepsDefault def UnknownDeps = def
154159

155160
mapResultDeps :: (KeySet -> KeySet) -> ResultDeps -> ResultDeps
156-
mapResultDeps f (ResultDeps ids) = ResultDeps $ f ids
161+
mapResultDeps f (ResultDeps ids) = ResultDeps $ fmap f ids
157162
mapResultDeps f (AlwaysRerunDeps ids) = AlwaysRerunDeps $ f ids
158163
mapResultDeps _ UnknownDeps = UnknownDeps
159164

Diff for: hls-graph/test/ActionSpec.hs

+29-5
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,17 @@
33

44
module ActionSpec where
55

6+
import qualified Control.Concurrent as C
67
import Control.Concurrent.STM
7-
import Development.IDE.Graph (shakeOptions)
8-
import Development.IDE.Graph.Database (shakeNewDatabase,
9-
shakeRunDatabase)
8+
import Development.IDE.Graph (shakeOptions)
9+
import Development.IDE.Graph.Database (shakeNewDatabase,
10+
shakeRunDatabase)
11+
import Development.IDE.Graph.Internal.Database (build, incDatabase)
1012
import Development.IDE.Graph.Internal.Key
1113
import Development.IDE.Graph.Internal.Types
1214
import Development.IDE.Graph.Rule
1315
import Example
14-
import qualified StmContainers.Map as STM
16+
import qualified StmContainers.Map as STM
1517
import Test.Hspec
1618

1719
spec :: Spec
@@ -40,7 +42,7 @@ spec = do
4042
apply1 theKey
4143
res `shouldBe` [True]
4244
Just (Clean res) <- lookup (newKey theKey) <$> getDatabaseValues theDb
43-
resultDeps res `shouldBe` ResultDeps (singletonKeySet $ newKey (Rule @()))
45+
resultDeps res `shouldBe` ResultDeps [singletonKeySet $ newKey (Rule @())]
4446
it "tracks reverse dependencies" $ do
4547
db@(ShakeDatabase _ _ Database {..}) <- shakeNewDatabase shakeOptions $ do
4648
ruleUnit
@@ -57,6 +59,28 @@ spec = do
5759
addRule $ \(Rule :: Rule ()) _old _mode -> error "boom"
5860
let res = shakeRunDatabase db $ pure $ apply1 (Rule @())
5961
res `shouldThrow` anyErrorCall
62+
it "computes a rule with branching dependencies does not invoke phantom dependencies #3423" $ do
63+
cond <- C.newMVar True
64+
count <- C.newMVar 0
65+
(ShakeDatabase _ _ theDb) <- shakeNewDatabase shakeOptions $ do
66+
ruleUnit
67+
ruleCond cond
68+
ruleSubBranch count
69+
ruleWithCond
70+
-- build the one with the condition True
71+
-- This should call the SubBranchRule once
72+
-- cond rule would return different results each time
73+
res0 <- build theDb emptyStack [BranchedRule]
74+
snd res0 `shouldBe` [1 :: Int]
75+
incDatabase theDb Nothing
76+
-- build the one with the condition False
77+
-- This should not call the SubBranchRule
78+
res1 <- build theDb emptyStack [BranchedRule]
79+
snd res1 `shouldBe` [2 :: Int]
80+
-- SubBranchRule should be recomputed once before this (when the condition was True)
81+
countRes <- build theDb emptyStack [SubBranchRule]
82+
snd countRes `shouldBe` [1 :: Int]
83+
6084
describe "applyWithoutDependency" $ do
6185
it "does not track dependencies" $ do
6286
db@(ShakeDatabase _ _ theDb) <- shakeNewDatabase shakeOptions $ do

Diff for: hls-graph/test/Example.hs

+35
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,8 @@
44
{-# LANGUAGE TypeFamilies #-}
55
module Example where
66

7+
import qualified Control.Concurrent as C
8+
import Control.Monad.IO.Class (liftIO)
79
import Development.IDE.Graph
810
import Development.IDE.Graph.Classes
911
import Development.IDE.Graph.Rule
@@ -27,3 +29,36 @@ ruleBool :: Rules ()
2729
ruleBool = addRule $ \Rule _old _mode -> do
2830
() <- apply1 Rule
2931
return $ RunResult ChangedRecomputeDiff "" True
32+
33+
34+
data CondRule = CondRule
35+
deriving (Eq, Generic, Hashable, NFData, Show, Typeable)
36+
type instance RuleResult CondRule = Bool
37+
38+
39+
ruleCond :: C.MVar Bool -> Rules ()
40+
ruleCond mv = addRule $ \CondRule _old _mode -> do
41+
r <- liftIO $ C.modifyMVar mv $ \x -> return (not x, x)
42+
return $ RunResult ChangedRecomputeDiff "" r
43+
44+
data BranchedRule = BranchedRule
45+
deriving (Eq, Generic, Hashable, NFData, Show, Typeable)
46+
type instance RuleResult BranchedRule = Int
47+
48+
ruleWithCond :: Rules ()
49+
ruleWithCond = addRule $ \BranchedRule _old _mode -> do
50+
r <- apply1 CondRule
51+
if r then do
52+
_ <- apply1 SubBranchRule
53+
return $ RunResult ChangedRecomputeDiff "" (1 :: Int)
54+
else
55+
return $ RunResult ChangedRecomputeDiff "" (2 :: Int)
56+
57+
data SubBranchRule = SubBranchRule
58+
deriving (Eq, Generic, Hashable, NFData, Show, Typeable)
59+
type instance RuleResult SubBranchRule = Int
60+
61+
ruleSubBranch :: C.MVar Int -> Rules ()
62+
ruleSubBranch mv = addRule $ \SubBranchRule _old _mode -> do
63+
r <- liftIO $ C.modifyMVar mv $ \x -> return (x+1, x)
64+
return $ RunResult ChangedRecomputeDiff "" r

0 commit comments

Comments
 (0)