Skip to content

Commit da6230f

Browse files
committed
implement reverse deps
1 parent 76eb0a1 commit da6230f

File tree

10 files changed

+155
-126
lines changed

10 files changed

+155
-126
lines changed

ghcide/src/Development/IDE/Core/FileStore.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,6 @@ import Development.IDE.Import.DependencyInformation
4848
import Development.IDE.Types.Diagnostics
4949
import Development.IDE.Types.Location
5050
import Development.IDE.Types.Options
51-
import Development.IDE.Types.Shake (SomeShakeValue)
5251
import HieDb.Create (deleteMissingRealFiles)
5352
import Ide.Plugin.Config (CheckParents (..),
5453
Config)
@@ -294,7 +293,7 @@ typecheckParentsAction nfp = do
294293
-- | Note that some keys have been modified and restart the session
295294
-- Only valid if the virtual file system was initialised by LSP, as that
296295
-- independently tracks which files are modified.
297-
setSomethingModified :: IdeState -> [SomeShakeValue] -> IO ()
296+
setSomethingModified :: IdeState -> [Key] -> IO ()
298297
setSomethingModified state keys = do
299298
VFSHandle{..} <- getIdeGlobalState state
300299
when (isJust setVirtualFileContents) $

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -214,7 +214,7 @@ data ShakeExtras = ShakeExtras
214214
, vfs :: VFSHandle
215215
, defaultConfig :: Config
216216
-- ^ Default HLS config, only relevant if the client does not provide any Config
217-
, dirtyKeys :: IORef (HashSet SomeShakeValue)
217+
, dirtyKeys :: IORef (HashSet Key)
218218
-- ^ Set of dirty rule keys since the last Shake run
219219
}
220220

ghcide/src/Development/IDE/Types/Shake.hs

Lines changed: 5 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@ module Development.IDE.Types.Shake
88
ValueWithDiagnostics (..),
99
Values,
1010
Key (..),
11-
SomeShakeValue,
1211
BadDependency (..),
1312
ShakeValue(..),
1413
currentValue,
@@ -22,14 +21,12 @@ import qualified Data.ByteString.Char8 as BS
2221
import Data.Dynamic
2322
import Data.HashMap.Strict
2423
import Data.Hashable
25-
import Data.Typeable
2624
import Data.Vector (Vector)
2725
import Development.IDE.Core.PositionMapping
28-
import Development.IDE.Graph (RuleResult,
26+
import Development.IDE.Graph (Key (..), RuleResult,
2927
ShakeException (shakeExceptionInner))
3028
import qualified Development.IDE.Graph as Shake
3129
import Development.IDE.Graph.Classes
32-
import Development.IDE.Graph.Database (SomeShakeValue (..))
3330
import Development.IDE.Types.Diagnostics
3431
import Development.IDE.Types.Location
3532
import GHC.Generics
@@ -56,26 +53,6 @@ data ValueWithDiagnostics
5653
-- | The state of the all values and diagnostics
5754
type Values = HashMap (NormalizedFilePath, Key) ValueWithDiagnostics
5855

59-
-- | Key type
60-
data Key = forall k . (Typeable k, Hashable k, Eq k, NFData k, Show k) => Key k
61-
62-
instance Show Key where
63-
show (Key k) = show k
64-
65-
instance Eq Key where
66-
Key k1 == Key k2 | Just k2' <- cast k2 = k1 == k2'
67-
| otherwise = False
68-
69-
instance Hashable Key where
70-
hashWithSalt salt (Key key) = hashWithSalt salt key
71-
72-
instance Binary Key where
73-
get = error "not really"
74-
put _ = error "not really"
75-
76-
instance NFData Key where
77-
rnf (Key k) = rnf k
78-
7956
-- | When we depend on something that reported an error, and we fail as a direct result, throw BadDependency
8057
-- which short-circuits the rest of the action
8158
newtype BadDependency = BadDependency String deriving Show
@@ -87,12 +64,11 @@ isBadDependency x
8764
| Just (_ :: BadDependency) <- fromException x = True
8865
| otherwise = False
8966

67+
toKey :: Shake.ShakeValue k => k -> NormalizedFilePath -> Key
68+
toKey = (Key.) . curry Q
9069

91-
toKey :: Shake.ShakeValue k => k -> NormalizedFilePath -> SomeShakeValue
92-
toKey = (SomeShakeValue .) . curry Q
93-
94-
toNoFileKey :: (Show k, Typeable k, Eq k, Hashable k, Binary k, NFData k) => k -> SomeShakeValue
95-
toNoFileKey k = toKey k emptyFilePath
70+
toNoFileKey :: (Show k, Typeable k, Eq k, Hashable k, Binary k) => k -> Key
71+
toNoFileKey k = Key $ Q (k, emptyFilePath)
9672

9773
newtype Q k = Q (k, NormalizedFilePath)
9874
deriving newtype (Eq, Hashable, NFData)

hls-graph/hls-graph.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -45,6 +45,7 @@ library
4545
, async
4646
, base >=4.12 && <5
4747
, bytestring
48+
, containers
4849
, extra
4950
, primitive
5051
, shake >= 0.19.4

hls-graph/src/Development/IDE/Graph.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ module Development.IDE.Graph(
44
shakeOptions,
55
Rules,
66
Action, action,
7+
Key(..),
78
actionFinally, actionBracket, actionCatch,
89
Shake.ShakeException(..),
910
-- * Configuration

hls-graph/src/Development/IDE/Graph/Database.hs

Lines changed: 6 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44
module Development.IDE.Graph.Database(
55
ShakeDatabase,
66
ShakeValue,
7-
SomeShakeValue(..),
87
shakeOpenDatabase,
98
shakeRunDatabase,
109
shakeRunDatabaseForKeys,
@@ -13,7 +12,6 @@ module Development.IDE.Graph.Database(
1312

1413
import Data.Dynamic
1514
import Data.Maybe
16-
import Data.Typeable (cast)
1715
import Development.IDE.Graph.Classes
1816
import Development.IDE.Graph.Internal.Action
1917
import Development.IDE.Graph.Internal.Database
@@ -37,10 +35,7 @@ shakeNewDatabase opts rules = do
3735
pure $ ShakeDatabase (length actions) actions db
3836

3937
shakeRunDatabase :: ShakeDatabase -> [Action a] -> IO ([a], [IO ()])
40-
shakeRunDatabase (ShakeDatabase lenAs1 as1 db) as2 = do
41-
incDatabase db
42-
as <- fmap (drop lenAs1) $ runActions db $ map unvoid as1 ++ as2
43-
return (as, [])
38+
shakeRunDatabase = shakeRunDatabaseForKeys Nothing
4439

4540
-- Only valid if we never pull on the results, which we don't
4641
unvoid :: Functor m => m () -> m a
@@ -50,20 +45,15 @@ unvoid = fmap undefined
5045
shakeProfileDatabase :: ShakeDatabase -> FilePath -> IO ()
5146
shakeProfileDatabase _ file = writeFile file ""
5247

53-
data SomeShakeValue = forall k . ShakeValue k => SomeShakeValue k
54-
instance Eq SomeShakeValue where SomeShakeValue a == SomeShakeValue b = cast a == Just b
55-
instance Hashable SomeShakeValue where hashWithSalt s (SomeShakeValue x) = hashWithSalt s x
56-
instance Show SomeShakeValue where show (SomeShakeValue x) = show x
57-
5848
type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, NFData a, Binary a)
5949

6050
shakeRunDatabaseForKeys
61-
:: Maybe [SomeShakeValue]
51+
:: Maybe [Key]
6252
-- ^ Set of keys changed since last run. 'Nothing' means everything has changed
6353
-> ShakeDatabase
6454
-> [Action a]
6555
-> IO ([a], [IO ()])
66-
shakeRunDatabaseForKeys _keys a b =
67-
-- Shake upstream does not accept the set of keys changed yet
68-
-- https://github.com/ndmitchell/shake/pull/802
69-
shakeRunDatabase a b
56+
shakeRunDatabaseForKeys keysChanged (ShakeDatabase lenAs1 as1 db) as2 = do
57+
incDatabase db keysChanged
58+
as <- fmap (drop lenAs1) $ runActions db $ map unvoid as1 ++ as2
59+
return (as, [])

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

Lines changed: 72 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -7,17 +7,23 @@
77
{-# LANGUAGE ScopedTypeVariables #-}
88
{-# LANGUAGE TupleSections #-}
99
{-# LANGUAGE TypeFamilies #-}
10+
{-# LANGUAGE ViewPatterns #-}
1011

1112
module Development.IDE.Graph.Internal.Database where
1213

1314
import Control.Concurrent.Async
1415
import Control.Concurrent.Extra
1516
import Control.Exception
1617
import Control.Monad
18+
import Control.Monad.Trans.Class (lift)
1719
import Control.Monad.Trans.Reader
20+
import qualified Control.Monad.Trans.State.Strict as State
1821
import Data.Dynamic
1922
import Data.Either
23+
import Data.Foldable (traverse_)
2024
import Data.IORef.Extra
25+
import Data.IntSet (IntSet)
26+
import qualified Data.IntSet as Set
2127
import Data.Maybe
2228
import Data.Tuple.Extra
2329
import qualified Development.IDE.Graph.Internal.Ids as Ids
@@ -36,17 +42,31 @@ newDatabase databaseExtra databaseRules = do
3642
databaseLock <- newLock
3743
databaseIds <- newIORef Intern.empty
3844
databaseValues <- Ids.empty
45+
databaseReverseDeps <- Ids.empty
46+
databaseReverseDepsLock <- newLock
3947
pure Database{..}
4048

41-
-- | Increment the step and mark all ids dirty
42-
incDatabase :: Database -> IO ()
43-
incDatabase db = do
44-
modifyIORef' (databaseStep db) $ \(Step i) -> Step $ i + 1
49+
-- | Increment the step and mark dirty
50+
incDatabase :: Database -> Maybe [Key] -> IO ()
51+
-- all keys are dirty
52+
incDatabase db Nothing =
4553
withLock (databaseLock db) $
46-
Ids.forMutate (databaseValues db) $ second $ \case
54+
Ids.forMutate (databaseValues db) $ \_ -> second $ \case
4755
Clean x -> Dirty (Just x)
4856
Dirty x -> Dirty x
4957
Running _ x -> Dirty x
58+
-- only some keys are dirty
59+
incDatabase db (Just kk) = do
60+
modifyIORef' (databaseStep db) $ \(Step i) -> Step $ i + 1
61+
intern <- readIORef (databaseIds db)
62+
let dirtyIds = mapMaybe (`Intern.lookup` intern) kk
63+
transitiveDirtyIds <- transitiveDirtySet db dirtyIds
64+
withLock (databaseLock db) $
65+
Ids.forMutate (databaseValues db) $ \i -> \case
66+
(k, Running _ x) -> (k, Dirty x)
67+
(k, Clean x) | i `Set.member` transitiveDirtyIds ->
68+
(k, Dirty (Just x))
69+
other -> other
5070

5171

5272
-- | Unwrap and build a list of keys in parallel
@@ -116,17 +136,17 @@ builder db@Database{..} keys = do
116136
cleanupAsync :: IORef [Async a] -> IO ()
117137
cleanupAsync ref = mapConcurrently_ uninterruptibleCancel =<< readIORef ref
118138

119-
120139
-- | Check if we need to run the database.
121140
check :: Database -> Key -> Id -> Maybe Result -> IO Result
122141
check db key id result@(Just me@Result{resultDeps=Just deps}) = do
123-
res <- builder db $ map Left deps
124-
let dirty = any (\(_,dep) -> resultBuilt me < resultChanged dep) res
125-
let mode = if dirty then Shake.RunDependenciesChanged else Shake.RunDependenciesSame
142+
mode <- do
143+
res <- builder db (map Left deps)
144+
let dirty = any (\(_,dep) -> resultBuilt me < resultChanged dep) res
145+
return $ if dirty then Shake.RunDependenciesChanged else Shake.RunDependenciesSame
146+
-- If I am not dirty then none of my dependencies are, so they must be unchanged
126147
spawn db key id mode result
127148
check db key id result = spawn db key id Shake.RunDependenciesChanged result
128149

129-
130150
-- | Spawn a new computation to run the action.
131151
spawn :: Database -> Key -> Id -> Shake.RunMode -> Maybe Result -> IO Result
132152
spawn db@Database{..} key id mode result = do
@@ -137,10 +157,11 @@ spawn db@Database{..} key id mode result = do
137157
deps <- readIORef deps
138158
let changed = if runChanged == Shake.ChangedRecomputeDiff then built else maybe built resultChanged result
139159
-- only update the deps when the rule ran with changes
140-
let actual_deps = if runChanged /= Shake.ChangedNothing then deps else previousDeps
160+
let actualDeps = if runChanged /= Shake.ChangedNothing then deps else previousDeps
141161
previousDeps= resultDeps =<< result
142-
let res = Result runValue built changed actual_deps runStore
143-
withLock databaseLock $
162+
let res = Result runValue built changed actualDeps runStore
163+
withLock databaseLock $ do
164+
updateReverseDeps id db (fromMaybe [] previousDeps) (fromMaybe [] actualDeps)
144165
Ids.insert databaseValues id (key, Clean res)
145166
pure res
146167

@@ -152,3 +173,41 @@ splitIO act = do
152173
let act2 = Box <$> act
153174
let res = unsafePerformIO act2
154175
(void $ evaluate res, fromBox res)
176+
177+
--------------------------------------------------------------------------------
178+
-- Reverse dependencies
179+
180+
-- | Update the reverse dependencies of an Id
181+
updateReverseDeps
182+
:: Id -- ^ Id
183+
-> Database
184+
-> [Id] -- ^ Previous direct dependencies of Id
185+
-> [Id] -- ^ Current direct dependencies of Id
186+
-> IO ()
187+
updateReverseDeps myId db prev new = do
188+
forM_ prev $ doOne (Set.delete $ idToInt myId)
189+
forM_ new $ doOne (Set.insert $ idToInt myId)
190+
where
191+
doOne f id = withLock (databaseReverseDepsLock db) $ do
192+
rdeps <- getReverseDependencies db id
193+
Ids.insert (databaseReverseDeps db) id (f $ fromMaybe mempty rdeps)
194+
195+
idToInt :: Id -> Int
196+
idToInt = id
197+
198+
getReverseDependencies :: Database -> Id -> IO (Maybe (IntSet))
199+
getReverseDependencies db = Ids.lookup (databaseReverseDeps db)
200+
201+
transitiveDirtySet :: Foldable t => Database -> t Id -> IO IntSet
202+
transitiveDirtySet database = flip State.execStateT Set.empty . traverse_ loop
203+
where
204+
loop (idToInt -> x) = do
205+
seen <- State.get
206+
if x `Set.member` seen then pure () else do
207+
State.put (Set.insert x seen)
208+
next <- lift $ getReverseDependencies database x
209+
traverse_ loop (maybe mempty Set.toList next)
210+
211+
212+
idFromInt :: Set.Key -> Id
213+
idFromInt = id

0 commit comments

Comments
 (0)