Skip to content

Commit

Permalink
Introduce KeyMap and KeySet
Browse files Browse the repository at this point in the history
  • Loading branch information
wz1000 committed Oct 19, 2022
1 parent c1ba145 commit 5ef5975
Show file tree
Hide file tree
Showing 12 changed files with 188 additions and 80 deletions.
1 change: 1 addition & 0 deletions .hlint.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@
- Development.IDE.Graph.Internal.Database
- Development.IDE.Graph.Internal.Paths
- Development.IDE.Graph.Internal.Profile
- Development.IDE.Graph.Internal.Types
- Ide.Types
- Test.Hls
- Test.Hls.Command
Expand Down
3 changes: 1 addition & 2 deletions ghcide/src/Development/IDE/Core/FileStore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,6 @@ import qualified Development.IDE.Types.Logger as L

import qualified Data.Binary as B
import qualified Data.ByteString.Lazy as LBS
import qualified Data.HashSet as HSet
import Data.List (foldl')
import qualified Data.Text as Text
import Development.IDE.Core.IdeConfiguration (isWorkspaceFile)
Expand Down Expand Up @@ -256,7 +255,7 @@ setSomethingModified vfs state keys reason = do
atomically $ do
writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) (\withHieDb -> withHieDb deleteMissingRealFiles)
modifyTVar' (dirtyKeys $ shakeExtras state) $ \x ->
foldl' (flip HSet.insert) x keys
foldl' (flip insertKeySet) x keys
void $ restartShakeSession (shakeExtras state) vfs reason []

registerFileWatches :: [String] -> LSP.LspT Config IO Bool
Expand Down
28 changes: 14 additions & 14 deletions ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -178,7 +178,7 @@ import System.Time.Extra
data Log
= LogCreateHieDbExportsMapStart
| LogCreateHieDbExportsMapFinish !Int
| LogBuildSessionRestart !String ![DelayedActionInternal] !(HashSet Key) !Seconds !(Maybe FilePath)
| LogBuildSessionRestart !String ![DelayedActionInternal] !(KeySet) !Seconds !(Maybe FilePath)
| LogBuildSessionRestartTakingTooLong !Seconds
| LogDelayedAction !(DelayedAction ()) !Seconds
| LogBuildSessionFinish !(Maybe SomeException)
Expand All @@ -197,7 +197,7 @@ instance Pretty Log where
vcat
[ "Restarting build session due to" <+> pretty reason
, "Action Queue:" <+> pretty (map actionName actionQueue)
, "Keys:" <+> pretty (map show $ HSet.toList keyBackLog)
, "Keys:" <+> pretty (map show $ toListKeySet keyBackLog)
, "Aborting previous build session took" <+> pretty (showDuration abortDuration) <+> pretty shakeProfilePath ]
LogBuildSessionRestartTakingTooLong seconds ->
"Build restart is taking too long (" <> pretty seconds <> " seconds)"
Expand Down Expand Up @@ -279,7 +279,7 @@ data ShakeExtras = ShakeExtras
,clientCapabilities :: ClientCapabilities
, withHieDb :: WithHieDb -- ^ Use only to read.
, hiedbWriter :: HieDbWriter -- ^ use to write
, persistentKeys :: TVar (HMap.HashMap Key GetStalePersistent)
, persistentKeys :: TVar (KeyMap GetStalePersistent)
-- ^ Registery for functions that compute/get "stale" results for the rule
-- (possibly from disk)
, vfsVar :: TVar VFS
Expand All @@ -290,7 +290,7 @@ data ShakeExtras = ShakeExtras
-- We don't need a STM.Map because we never update individual keys ourselves.
, defaultConfig :: Config
-- ^ Default HLS config, only relevant if the client does not provide any Config
, dirtyKeys :: TVar (HashSet Key)
, dirtyKeys :: TVar KeySet
-- ^ Set of dirty rule keys since the last Shake run
}

Expand Down Expand Up @@ -324,7 +324,7 @@ getPluginConfig plugin = do
addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,TextDocumentVersion))) -> Rules ()
addPersistentRule k getVal = do
ShakeExtras{persistentKeys} <- getShakeExtrasRules
void $ liftIO $ atomically $ modifyTVar' persistentKeys $ HMap.insert (newKey k) (fmap (fmap (first3 toDyn)) . getVal)
void $ liftIO $ atomically $ modifyTVar' persistentKeys $ insertKeyMap (newKey k) (fmap (fmap (first3 toDyn)) . getVal)

class Typeable a => IsIdeGlobal a where

Expand Down Expand Up @@ -399,7 +399,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
pmap <- readTVarIO persistentKeys
mv <- runMaybeT $ do
liftIO $ Logger.logDebug (logger s) $ T.pack $ "LOOKUP PERSISTENT FOR: " ++ show k
f <- MaybeT $ pure $ HMap.lookup (newKey k) pmap
f <- MaybeT $ pure $ lookupKeyMap (newKey k) pmap
(dv,del,ver) <- MaybeT $ runIdeAction "lastValueIO" s $ f file
MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
case mv of
Expand Down Expand Up @@ -509,7 +509,7 @@ deleteValue
-> STM ()
deleteValue ShakeExtras{dirtyKeys, state} key file = do
STM.delete (toKey key file) state
modifyTVar' dirtyKeys $ HSet.insert (toKey key file)
modifyTVar' dirtyKeys $ insertKeySet (toKey key file)

recordDirtyKeys
:: Shake.ShakeValue k
Expand All @@ -518,7 +518,7 @@ recordDirtyKeys
-> [NormalizedFilePath]
-> STM (IO ())
recordDirtyKeys ShakeExtras{dirtyKeys} key file = do
modifyTVar' dirtyKeys $ \x -> foldl' (flip HSet.insert) x (toKey key <$> file)
modifyTVar' dirtyKeys $ \x -> foldl' (flip insertKeySet) x (toKey key <$> file)
return $ withEventTrace "recordDirtyKeys" $ \addEvent -> do
addEvent (fromString $ unlines $ "dirty " <> show key : map fromNormalizedFilePath file)

Expand Down Expand Up @@ -594,7 +594,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
positionMapping <- STM.newIO
knownTargetsVar <- newTVarIO $ hashed HMap.empty
let restartShakeSession = shakeRestart recorder ideState
persistentKeys <- newTVarIO HMap.empty
persistentKeys <- newTVarIO mempty
indexPending <- newTVarIO HMap.empty
indexCompleted <- newTVarIO 0
indexProgressToken <- newVar Nothing
Expand Down Expand Up @@ -637,7 +637,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer

-- monitoring
let readValuesCounter = fromIntegral . countRelevantKeys checkParents <$> getStateKeys shakeExtras
readDirtyKeys = fromIntegral . countRelevantKeys checkParents . HSet.toList <$> readTVarIO(dirtyKeys shakeExtras)
readDirtyKeys = fromIntegral . countRelevantKeys checkParents . toListKeySet <$> readTVarIO(dirtyKeys shakeExtras)
readIndexPending = fromIntegral . HMap.size <$> readTVarIO (indexPending $ hiedbWriter shakeExtras)
readExportsMap = fromIntegral . HMap.size . getExportsMap <$> readTVarIO (exportsMap shakeExtras)
readDatabaseCount = fromIntegral . countRelevantKeys checkParents . map fst <$> shakeGetDatabaseKeys shakeDb
Expand Down Expand Up @@ -797,10 +797,10 @@ newSession recorder extras@ShakeExtras{..} vfsMod shakeDb acts reason = do
workRun restore = withSpan "Shake session" $ \otSpan -> do
setTag otSpan "reason" (fromString reason)
setTag otSpan "queue" (fromString $ unlines $ map actionName reenqueued)
whenJust allPendingKeys $ \kk -> setTag otSpan "keys" (BS8.pack $ unlines $ map show $ toList kk)
whenJust allPendingKeys $ \kk -> setTag otSpan "keys" (BS8.pack $ unlines $ map show $ toListKeySet kk)
let keysActs = pumpActionThread otSpan : map (run otSpan) (reenqueued ++ acts)
res <- try @SomeException $
restore $ shakeRunDatabaseForKeys (HSet.toList <$> allPendingKeys) shakeDb keysActs
restore $ shakeRunDatabaseForKeys (toListKeySet <$> allPendingKeys) shakeDb keysActs
return $ do
let exception =
case res of
Expand Down Expand Up @@ -890,7 +890,7 @@ garbageCollectKeys label maxAge checkParents agedKeys = do
= atomicallyNamed "GC" $ do
gotIt <- STM.focus (Focus.member <* Focus.delete) k values
when gotIt $
modifyTVar' dk (HSet.insert k)
modifyTVar' dk (insertKeySet k)
return $ if gotIt then (counter+1, k:keys) else st
| otherwise = pure st

Expand Down Expand Up @@ -1160,7 +1160,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
(if eq then ChangedRecomputeSame else ChangedRecomputeDiff)
(encodeShakeValue bs) $
A res
liftIO $ atomicallyNamed "define - dirtyKeys" $ modifyTVar' dirtyKeys (HSet.delete $ toKey key file)
liftIO $ atomicallyNamed "define - dirtyKeys" $ modifyTVar' dirtyKeys (deleteKeySet $ toKey key file)
return res
where
-- Highly unsafe helper to compute the version of a file
Expand Down
2 changes: 2 additions & 0 deletions hls-graph/hls-graph.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,8 @@ library
Development.IDE.Graph.Classes
Development.IDE.Graph.Database
Development.IDE.Graph.Rule
Development.IDE.Graph.KeyMap
Development.IDE.Graph.KeySet
Development.IDE.Graph.Internal.Action
Development.IDE.Graph.Internal.Options
Development.IDE.Graph.Internal.Rules
Expand Down
4 changes: 4 additions & 0 deletions hls-graph/src/Development/IDE/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,9 +20,13 @@ module Development.IDE.Graph(
-- * Actions for inspecting the keys in the database
getDirtySet,
getKeysAndVisitedAge,
module Development.IDE.Graph.KeyMap,
module Development.IDE.Graph.KeySet,
) where

import Development.IDE.Graph.Database
import Development.IDE.Graph.KeyMap
import Development.IDE.Graph.KeySet
import Development.IDE.Graph.Internal.Action
import Development.IDE.Graph.Internal.Options
import Development.IDE.Graph.Internal.Rules
Expand Down
2 changes: 1 addition & 1 deletion hls-graph/src/Development/IDE/Graph/Database.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,7 @@ shakeGetBuildEdges :: ShakeDatabase -> IO Int
shakeGetBuildEdges (ShakeDatabase _ _ db) = do
keys <- getDatabaseValues db
let ress = mapMaybe (getResult . snd) keys
return $ sum $ map (length . getResultDepsDefault mempty . resultDeps) ress
return $ sum $ map (lengthKeySet . getResultDepsDefault mempty . resultDeps) ress

-- | Returns an approximation of the database keys,
-- annotated with how long ago (in # builds) they were visited
Expand Down
3 changes: 1 addition & 2 deletions hls-graph/src/Development/IDE/Graph/Internal/Action.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,6 @@ import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Data.Foldable (toList)
import Data.Functor.Identity
import qualified Data.HashSet as HSet
import Data.IORef
import Development.IDE.Graph.Classes
import Development.IDE.Graph.Internal.Database
Expand Down Expand Up @@ -122,7 +121,7 @@ apply ks = do
stack <- Action $ asks actionStack
(is, vs) <- liftIO $ build db stack ks
ref <- Action $ asks actionDeps
liftIO $ modifyIORef ref (ResultDeps (HSet.fromList $ toList is) <>)
liftIO $ modifyIORef ref (ResultDeps (fromListKeySet $ toList is) <>)
pure vs

-- | Evaluate a list of keys without recording any dependencies.
Expand Down
32 changes: 15 additions & 17 deletions hls-graph/src/Development/IDE/Graph/Internal/Database.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,6 @@ import qualified Control.Monad.Trans.State.Strict as State
import Data.Dynamic
import Data.Either
import Data.Foldable (for_, traverse_)
import Data.HashSet (HashSet)
import qualified Data.HashSet as HSet
import Data.IORef.Extra
import Data.List.NonEmpty (unzip)
import Data.Maybe
Expand Down Expand Up @@ -61,7 +59,7 @@ incDatabase :: Database -> Maybe [Key] -> IO ()
incDatabase db (Just kk) = do
atomicallyNamed "incDatabase" $ modifyTVar' (databaseStep db) $ \(Step i) -> Step $ i + 1
transitiveDirtyKeys <- transitiveDirtySet db kk
for_ transitiveDirtyKeys $ \k ->
for_ (toListKeySet transitiveDirtyKeys) $ \k ->
-- Updating all the keys atomically is not necessary
-- since we assume that no build is mutating the db.
-- Therefore run one transaction per key to minimise contention.
Expand Down Expand Up @@ -146,7 +144,7 @@ refresh :: Database -> Stack -> Key -> Maybe Result -> AIO (IO Result)
-- refresh _ st k _ | traceShow ("refresh", st, k) False = undefined
refresh db stack key result = case (addStack key stack, result) of
(Left e, _) -> throw e
(Right stack, Just me@Result{resultDeps = ResultDeps (HSet.toList -> deps)}) -> do
(Right stack, Just me@Result{resultDeps = ResultDeps (toListKeySet -> deps)}) -> do
res <- builder db stack deps
let isDirty = any (\(_,dep) -> resultBuilt me < resultChanged dep)
case res of
Expand Down Expand Up @@ -178,7 +176,7 @@ compute db@Database{..} stack key mode result = do
previousDeps= maybe UnknownDeps resultDeps result
let res = Result runValue built' changed built actualDeps execution runStore
case getResultDepsDefault mempty actualDeps of
deps | not(null deps)
deps | not(nullKeySet deps)
&& runChanged /= ChangedNothing
-> do
-- IMPORTANT: record the reverse deps **before** marking the key Clean.
Expand Down Expand Up @@ -236,15 +234,15 @@ splitIO act = do
updateReverseDeps
:: Key -- ^ Id
-> Database
-> HashSet Key -- ^ Previous direct dependencies of Id
-> HashSet Key -- ^ Current direct dependencies of Id
-> KeySet -- ^ Previous direct dependencies of Id
-> KeySet -- ^ Current direct dependencies of Id
-> IO ()
-- mask to ensure that all the reverse dependencies are updated
updateReverseDeps myId db prev new = do
forM_ (HSet.toList $ prev `HSet.difference` new) $ \d ->
doOne (HSet.delete myId) d
forM_ (HSet.toList new) $
doOne (HSet.insert myId)
forM_ (toListKeySet $ prev `differenceKeySet` new) $ \d ->
doOne (deleteKeySet myId) d
forM_ (toListKeySet new) $
doOne (insertKeySet myId)
where
alterRDeps f =
Focus.adjust (onKeyReverseDeps f)
Expand All @@ -254,18 +252,18 @@ updateReverseDeps myId db prev new = do
doOne f id = atomicallyNamed "updateReverseDeps" $
SMap.focus (alterRDeps f) id (databaseValues db)

getReverseDependencies :: Database -> Key -> STM (Maybe (HashSet Key))
getReverseDependencies :: Database -> Key -> STM (Maybe KeySet)
getReverseDependencies db = (fmap.fmap) keyReverseDeps . flip SMap.lookup (databaseValues db)

transitiveDirtySet :: Foldable t => Database -> t Key -> IO (HashSet Key)
transitiveDirtySet database = flip State.execStateT HSet.empty . traverse_ loop
transitiveDirtySet :: Foldable t => Database -> t Key -> IO KeySet
transitiveDirtySet database = flip State.execStateT mempty . traverse_ loop
where
loop x = do
seen <- State.get
if x `HSet.member` seen then pure () else do
State.put (HSet.insert x seen)
if x `memberKeySet` seen then pure () else do
State.put (insertKeySet x seen)
next <- lift $ atomically $ getReverseDependencies database x
traverse_ loop (maybe mempty HSet.toList next)
traverse_ loop (maybe mempty toListKeySet next)

--------------------------------------------------------------------------------
-- Asynchronous computations with cancellation
Expand Down
Loading

0 comments on commit 5ef5975

Please sign in to comment.