Skip to content

Commit a8bbd30

Browse files
authored
Merge branch 'master' into cleanup-dirtyset
2 parents dc259e9 + 9233be8 commit a8bbd30

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
@@ -135,7 +135,7 @@ builder db@Database{..} keys = do
135135
-- This assumes that the implementation will be a lookup
136136
-- * Otherwise, we spawn a new thread to refresh the dirty deps (if any) and the key itself
137137
refresh :: Database -> Key -> Id -> Maybe Result -> AIO (IO Result)
138-
refresh db key id result@(Just me@Result{resultDeps=Just deps}) = do
138+
refresh db key id result@(Just me@Result{resultDeps = ResultDeps deps}) = do
139139
res <- builder db $ map Left deps
140140
case res of
141141
Left res ->
@@ -157,7 +157,7 @@ refresh db key id result =
157157
compute :: Database -> Key -> Id -> RunMode -> Maybe Result -> IO Result
158158
compute db@Database{..} key id mode result = do
159159
let act = runRule databaseRules key (fmap resultData result) mode
160-
deps <- newIORef $ Just []
160+
deps <- newIORef UnknownDeps
161161
(execution, RunResult{..}) <-
162162
duration $ runReaderT (fromAction act) $ SAction db deps
163163
built <- readIORef databaseStep
@@ -166,14 +166,14 @@ compute db@Database{..} key id mode result = do
166166
built' = if runChanged /= ChangedNothing then built else changed
167167
-- only update the deps when the rule ran with changes
168168
actualDeps = if runChanged /= ChangedNothing then deps else previousDeps
169-
previousDeps= resultDeps =<< result
169+
previousDeps= maybe UnknownDeps resultDeps result
170170
let res = Result runValue built' changed built actualDeps execution runStore
171171
case actualDeps of
172-
Just deps | not(null deps) &&
172+
ResultDeps deps | not(null deps) &&
173173
runChanged /= ChangedNothing
174174
-> do
175175
void $ forkIO $
176-
updateReverseDeps id db (fromMaybe [] previousDeps) (Set.fromList deps)
176+
updateReverseDeps id db (getResultDepsDefault [] previousDeps) (Set.fromList deps)
177177
_ -> pure ()
178178
withLock databaseLock $
179179
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
@@ -61,7 +61,7 @@ data ProfileEntry = ProfileEntry
6161
-- resultsOnly :: Map.HashMap Id (Key, Status) -> Map.HashMap Id (Key, Result (Either BS.ByteString Value))
6262
resultsOnly :: [(Ids.Id, (k, Status))] -> Map.HashMap Ids.Id (k, Result)
6363
resultsOnly mp = Map.map (fmap (\r ->
64-
r{resultDeps = fmap (filter (isJust . flip Map.lookup keep)) $ resultDeps r}
64+
r{resultDeps = mapResultDeps (filter (isJust . flip Map.lookup keep)) $ resultDeps r}
6565
)) keep
6666
where
6767
keep = Map.fromList $ mapMaybe ((traverse.traverse) getResult) mp
@@ -113,7 +113,7 @@ toReport db = do
113113
status <- prepareForDependencyOrder db
114114
let order = let shw i = maybe "<unknown>" (show . fst) $ Map.lookup i status
115115
in dependencyOrder shw
116-
$ map (second (fromMaybe [-1] . resultDeps . snd))
116+
$ map (second (getResultDepsDefault [-1] . resultDeps . snd))
117117
$ Map.toList status
118118
ids = IntMap.fromList $ zip order [0..]
119119

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

135135
alwaysRerunResult :: Step -> Result
136-
alwaysRerunResult current = Result (Value $ toDyn "<alwaysRerun>") (Step 0) (Step 0) current (Just []) 0 mempty
136+
alwaysRerunResult current = Result (Value $ toDyn "<alwaysRerun>") (Step 0) (Step 0) current (ResultDeps []) 0 mempty
137137

138138
readDataFileHTML :: FilePath -> IO LBS.ByteString
139139
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
@@ -55,7 +55,7 @@ newtype Action a = Action {fromAction :: ReaderT SAction IO a}
5555

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

6161

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

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

0 commit comments

Comments
 (0)