Skip to content

Commit 9233be8

Browse files
authored
Fix reverse dep. tracking for alwaysRerun rules (#2298)
When I ported reverse dependencies from Shake[1] I missed an important detail. While Shake models alwaysRerun as a dependency on an actual rule (AlwaysRerun), hls-graph models alwaysRerun by setting actionDeps to Nothing. This is important because dependencies are not computed for these rules, and therefore reverse dependency tracking doesn't do anything, which breaks correctness of dirty rebuilds This commit adds dependency tracking for alwaysRerun rules, and fixes reverse dependency tracking. The alternative would be following the Shake approach but I'm not sure what other implications this might have. [1] - ndmitchell/shake#802
1 parent d44a706 commit 9233be8

File tree

4 files changed

+45
-25
lines changed

4 files changed

+45
-25
lines changed

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

Lines changed: 12 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
1+
{-# LANGUAGE ConstraintKinds #-}
12
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
23
{-# LANGUAGE ScopedTypeVariables #-}
34
{-# LANGUAGE TypeFamilies #-}
4-
{-# LANGUAGE ConstraintKinds #-}
55

66
module Development.IDE.Graph.Internal.Action
77
( ShakeValue
@@ -19,23 +19,23 @@ module Development.IDE.Graph.Internal.Action
1919

2020
import Control.Concurrent.Async
2121
import Control.Exception
22-
import Control.Monad.Extra
2322
import Control.Monad.IO.Class
2423
import Control.Monad.Trans.Class
2524
import Control.Monad.Trans.Reader
2625
import Data.IORef
2726
import Development.IDE.Graph.Classes
2827
import Development.IDE.Graph.Internal.Database
28+
import Development.IDE.Graph.Internal.Rules (RuleResult)
2929
import Development.IDE.Graph.Internal.Types
3030
import System.Exit
31-
import Development.IDE.Graph.Internal.Rules (RuleResult)
3231

3332
type ShakeValue a = (Show a, Typeable a, Eq a, Hashable a, NFData a)
3433

34+
-- | Always rerun this rule when dirty, regardless of the dependencies.
3535
alwaysRerun :: Action ()
3636
alwaysRerun = do
3737
ref <- Action $ asks actionDeps
38-
liftIO $ writeIORef ref Nothing
38+
liftIO $ modifyIORef ref (AlwaysRerunDeps [] <>)
3939

4040
-- No-op for now
4141
reschedule :: Double -> Action ()
@@ -48,23 +48,23 @@ parallel xs = do
4848
a <- Action ask
4949
deps <- liftIO $ readIORef $ actionDeps a
5050
case deps of
51-
Nothing ->
51+
UnknownDeps ->
5252
-- if we are already in the rerun mode, nothing we do is going to impact our state
5353
liftIO $ mapConcurrently (ignoreState a) xs
54-
Just deps -> do
54+
deps -> do
5555
(newDeps, res) <- liftIO $ unzip <$> mapConcurrently (usingState a) xs
56-
liftIO $ writeIORef (actionDeps a) $ (deps ++) <$> concatMapM id newDeps
56+
liftIO $ writeIORef (actionDeps a) $ mconcat $ deps : newDeps
5757
pure res
5858
where
5959
usingState a x = do
60-
ref <- newIORef $ Just []
60+
ref <- newIORef mempty
6161
res <- runReaderT (fromAction x) a{actionDeps=ref}
6262
deps <- readIORef ref
6363
pure (deps, res)
6464

6565
ignoreState :: SAction -> Action b -> IO b
6666
ignoreState a x = do
67-
ref <- newIORef Nothing
67+
ref <- newIORef mempty
6868
runReaderT (fromAction x) a{actionDeps=ref}
6969

7070
actionFork :: Action a -> (Async a -> Action b) -> Action b
@@ -73,7 +73,7 @@ actionFork act k = do
7373
deps <- liftIO $ readIORef $ actionDeps a
7474
let db = actionDatabase a
7575
case deps of
76-
Nothing -> do
76+
UnknownDeps -> do
7777
-- if we are already in the rerun mode, nothing we do is going to impact our state
7878
[res] <- liftIO $ withAsync (ignoreState a act) $ \as -> runActions db [k as]
7979
return res
@@ -116,12 +116,10 @@ apply ks = do
116116
db <- Action $ asks actionDatabase
117117
(is, vs) <- liftIO $ build db ks
118118
ref <- Action $ asks actionDeps
119-
deps <- liftIO $ readIORef ref
120-
whenJust deps $ \deps ->
121-
liftIO $ writeIORef ref $ Just $ is ++ deps
119+
liftIO $ modifyIORef ref (ResultDeps is <>)
122120
pure vs
123121

124122
runActions :: Database -> [Action a] -> IO [a]
125123
runActions db xs = do
126-
deps <- newIORef Nothing
124+
deps <- newIORef mempty
127125
runReaderT (fromAction $ parallel xs) $ SAction db deps

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

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ builder db@Database{..} keys = do
138138
-- This assumes that the implementation will be a lookup
139139
-- * Otherwise, we spawn a new thread to refresh the dirty deps (if any) and the key itself
140140
refresh :: Database -> Key -> Id -> Maybe Result -> AIO (IO Result)
141-
refresh db key id result@(Just me@Result{resultDeps=Just deps}) = do
141+
refresh db key id result@(Just me@Result{resultDeps = ResultDeps deps}) = do
142142
res <- builder db $ map Left deps
143143
case res of
144144
Left res ->
@@ -160,7 +160,7 @@ refresh db key id result =
160160
compute :: Database -> Key -> Id -> RunMode -> Maybe Result -> IO Result
161161
compute db@Database{..} key id mode result = do
162162
let act = runRule databaseRules key (fmap resultData result) mode
163-
deps <- newIORef $ Just []
163+
deps <- newIORef UnknownDeps
164164
(execution, RunResult{..}) <-
165165
duration $ runReaderT (fromAction act) $ SAction db deps
166166
built <- readIORef databaseStep
@@ -169,14 +169,14 @@ compute db@Database{..} key id mode result = do
169169
built' = if runChanged /= ChangedNothing then built else changed
170170
-- only update the deps when the rule ran with changes
171171
actualDeps = if runChanged /= ChangedNothing then deps else previousDeps
172-
previousDeps= resultDeps =<< result
172+
previousDeps= maybe UnknownDeps resultDeps result
173173
let res = Result runValue built' changed built actualDeps execution runStore
174174
case actualDeps of
175-
Just deps | not(null deps) &&
175+
ResultDeps deps | not(null deps) &&
176176
runChanged /= ChangedNothing
177177
-> do
178178
void $ forkIO $
179-
updateReverseDeps id db (fromMaybe [] previousDeps) (Set.fromList deps)
179+
updateReverseDeps id db (getResultDepsDefault [] previousDeps) (Set.fromList deps)
180180
_ -> pure ()
181181
withLock databaseLock $
182182
Ids.insert databaseValues id (key, Clean res)

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

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ data ProfileEntry = ProfileEntry
5757
-- resultsOnly :: Map.HashMap Id (Key, Status) -> Map.HashMap Id (Key, Result (Either BS.ByteString Value))
5858
resultsOnly :: [(Ids.Id, (k, Status))] -> Map.HashMap Ids.Id (k, Result)
5959
resultsOnly mp = Map.map (fmap (\r ->
60-
r{resultDeps = fmap (filter (isJust . flip Map.lookup keep)) $ resultDeps r}
60+
r{resultDeps = mapResultDeps (filter (isJust . flip Map.lookup keep)) $ resultDeps r}
6161
)) keep
6262
where
6363
keep = Map.fromList $ mapMaybe ((traverse.traverse) getResult) mp
@@ -109,7 +109,7 @@ toReport db = do
109109
status <- prepareForDependencyOrder db
110110
let order = let shw i = maybe "<unknown>" (show . fst) $ Map.lookup i status
111111
in dependencyOrder shw
112-
$ map (second (fromMaybe [-1] . resultDeps . snd))
112+
$ map (second (getResultDepsDefault [-1] . resultDeps . snd))
113113
$ Map.toList status
114114
ids = IntMap.fromList $ zip order [0..]
115115

@@ -122,14 +122,14 @@ toReport db = do
122122
,prfBuilt = fromStep resultBuilt
123123
,prfVisited = fromStep resultVisited
124124
,prfChanged = fromStep resultChanged
125-
,prfDepends = map pure $ mapMaybe (`IntMap.lookup` ids) $ fromMaybe [-1] $ resultDeps
125+
,prfDepends = map pure $ mapMaybe (`IntMap.lookup` ids) $ getResultDepsDefault [-1] resultDeps
126126
,prfExecution = resultExecution
127127
}
128128
where fromStep i = fromJust $ Map.lookup i steps
129129
pure ([maybe (error "toReport") f $ Map.lookup i status | i <- order], ids)
130130

131131
alwaysRerunResult :: Step -> Result
132-
alwaysRerunResult current = Result (Value $ toDyn "<alwaysRerun>") (Step 0) (Step 0) current (Just []) 0 mempty
132+
alwaysRerunResult current = Result (Value $ toDyn "<alwaysRerun>") (Step 0) (Step 0) current (ResultDeps []) 0 mempty
133133

134134
readDataFileHTML :: FilePath -> IO LBS.ByteString
135135
readDataFileHTML file = LBS.readFile =<< getDataFile ("html" </> file)

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

Lines changed: 24 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ newtype Action a = Action {fromAction :: ReaderT SAction IO a}
5454

5555
data SAction = SAction {
5656
actionDatabase :: !Database,
57-
actionDeps :: !(IORef (Maybe [Id])) -- Nothing means always rerun
57+
actionDeps :: !(IORef ResultDeps)
5858
}
5959

6060

@@ -106,11 +106,33 @@ data Result = Result {
106106
resultBuilt :: !Step, -- ^ the step when it was last recomputed
107107
resultChanged :: !Step, -- ^ the step when it last changed
108108
resultVisited :: !Step, -- ^ the step when it was last looked up
109-
resultDeps :: !(Maybe [Id]), -- ^ Nothing = alwaysRerun
109+
resultDeps :: !ResultDeps,
110110
resultExecution :: !Seconds, -- ^ How long it took, last time it ran
111111
resultData :: BS.ByteString
112112
}
113113

114+
data ResultDeps = UnknownDeps | AlwaysRerunDeps ![Id] | ResultDeps ![Id]
115+
116+
getResultDepsDefault :: [Id] -> ResultDeps -> [Id]
117+
getResultDepsDefault _ (ResultDeps ids) = ids
118+
getResultDepsDefault _ (AlwaysRerunDeps ids) = ids
119+
getResultDepsDefault def UnknownDeps = def
120+
121+
mapResultDeps :: ([Id] -> [Id]) -> ResultDeps -> ResultDeps
122+
mapResultDeps f (ResultDeps ids) = ResultDeps $ f ids
123+
mapResultDeps f (AlwaysRerunDeps ids) = AlwaysRerunDeps $ f ids
124+
mapResultDeps _ UnknownDeps = UnknownDeps
125+
126+
instance Semigroup ResultDeps where
127+
UnknownDeps <> x = x
128+
x <> UnknownDeps = x
129+
AlwaysRerunDeps ids <> x = AlwaysRerunDeps (ids <> getResultDepsDefault [] x)
130+
x <> AlwaysRerunDeps ids = AlwaysRerunDeps (getResultDepsDefault [] x <> ids)
131+
ResultDeps ids <> ResultDeps ids' = ResultDeps (ids <> ids')
132+
133+
instance Monoid ResultDeps where
134+
mempty = UnknownDeps
135+
114136
---------------------------------------------------------------------
115137
-- Running builds
116138

0 commit comments

Comments
 (0)