Skip to content

Commit

Permalink
Check dependencies for restoring dbs
Browse files Browse the repository at this point in the history
Summary:
If `atLeast` n dbs are missing their dependencies in manifold, we can end up with no db to restore. This happened in S448970 when we removed some of the `www.hack.light` dbs and no `www.hack.incr` were available in query server because all latest `atLeast` n `www.hack.incr` dbs were stacked on removed `www.hack.light`. However there were older dbs available to restore with available dependencies

This diff checks if db has dependency available before taking `atLeast` n dbs to restore. This way server will try to restore older available dbs if recent ones have missing dependencies

Reviewed By: donsbot, simonmar

Differential Revision: D65151032

fbshipit-source-id: 831303bb22de21d17f32bfa8604877f1c9dbf056
  • Loading branch information
iamirzhan authored and facebook-github-bot committed Oct 30, 2024
1 parent 6d41e34 commit b764242
Show file tree
Hide file tree
Showing 3 changed files with 60 additions and 8 deletions.
14 changes: 10 additions & 4 deletions glean/db/Glean/Database/Retention.hs
Original file line number Diff line number Diff line change
Expand Up @@ -184,7 +184,7 @@ computeRetentionSet
-> DbIndex
-> m [Item]
computeRetentionSet config_retention config_restore
time isAvailableM DbIndex{..} =
time isAvailableM dbIndex@DbIndex{..} =
transitiveClosureBy itemRepo (catMaybes . depsRestored) <$>
concatMapM allRetention byRepoName
where
Expand All @@ -200,7 +200,8 @@ computeRetentionSet config_retention config_restore
allRetention (repo, dbs) = do
let policies = repoRetention config_retention repo
uniqBy (comparing itemRepo) . concat <$>
mapM (\pol -> dbRetentionForRepo pol time isAvailableM dbs) policies
mapM (\pol ->
dbRetentionForRepo pol time isAvailableM dbs dbIndex) policies


-- | The target set of DBs we want usable on the disk. This is a set of
Expand All @@ -211,8 +212,9 @@ dbRetentionForRepo
-> UTCTime
-> (Item -> m Bool)
-> NonEmpty Item
-> DbIndex
-> m [Item]
dbRetentionForRepo ServerConfig.Retention{..} t isAvailableM dbs = do
dbRetentionForRepo ServerConfig.Retention{..} t isAvailableM dbs dbIndex = do
let
-- retention policy parameters
retainAtLeast' = fromIntegral $ fromMaybe 0 retention_retain_at_least
Expand All @@ -238,6 +240,7 @@ dbRetentionForRepo ServerConfig.Retention{..} t isAvailableM dbs = do
completenessStatus itemMeta == DatabaseStatus_Complete
isOlderThan secs Item{..} = dbAge t itemMeta >= secs
isAvailable = isLocal |||> isAvailableM
hasDependencies = not . missingDependencies dbIndex

-- all DBs with the required properties, sorted by most recent first
sorted =
Expand All @@ -254,7 +257,7 @@ dbRetentionForRepo ServerConfig.Retention{..} t isAvailableM dbs = do
-- ensure we have retain_at_least DBs from the available set
atLeast <- takeFilterM
retainAtLeast
(isComplete &&&> isAvailable)
(isComplete &&& hasDependencies &&&> isAvailable)
-- bound the search since isAvailable is expensive
-- this matters only for tier bootstraps where all DBs are unavailable
(take (retainAtLeast*10) sorted)
Expand All @@ -264,6 +267,9 @@ dbRetentionForRepo ServerConfig.Retention{..} t isAvailableM dbs = do

return $ uniqBy (comparing itemRepo) (atLeast ++ atMost)

missingDependencies :: DbIndex -> Item -> Bool
missingDependencies dbIndex item = any isNothing (dependencies dbIndex item)

hasProperties :: HashMap.HashMap Text Text -> Item -> Bool
hasProperties req Item{..} = all has (HashMap.toList req)
where
Expand Down
14 changes: 11 additions & 3 deletions glean/test/tests/Model/Command.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,13 +10,15 @@ module Model.Command where

import Data.Containers.ListUtils (nubOrd)
import Data.Int (Int64)
import Data.Text (pack)
import Data.Text (pack, Text)
import qualified Glean.Database.Storage as Storage
import Glean.Internal.Types (Completeness (..), Meta (..))
import Glean.Types (
DatabaseComplete (..),
Dependencies (..),
PosixEpochTime (PosixEpochTime),
Repo (Repo, repo_hash, repo_name),
Stacked (..)
)
import Model.Model (ShardId, numberOfShards)
import Test.QuickCheck (
Expand Down Expand Up @@ -82,8 +84,14 @@ instance Arbitrary ShardingAssignmentChange where
, ShardRemoved . showt <$> choose (0, numberOfShards)
]

defDependency :: Text -> Text -> Dependencies
defDependency name hash = Dependencies_stacked $ Stacked name hash Nothing

defMeta :: Meta
defMeta =
defMeta = defMetaWithDependency Nothing

defMetaWithDependency :: Maybe Dependencies -> Meta
defMetaWithDependency dependencies =
Meta
{ metaVersion = Storage.currentVersion
, metaCreated = PosixEpochTime 0
Expand All @@ -95,7 +103,7 @@ defMeta =
}
, metaBackup = Nothing
, metaProperties = mempty
, metaDependencies = Nothing
, metaDependencies = dependencies
, metaCompletePredicates = mempty
, metaAxiomComplete = False
, metaRepoHashTime = Nothing
Expand Down
40 changes: 39 additions & 1 deletion glean/test/tests/Model/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ import qualified Glean.ServerConfig.Types as ServerTypes
import Glean.Test.Mock (Mock, augment, call, implement, reimplement)
import Glean.Types (
Database (Database),
DatabaseStatus (DatabaseStatus_Restoring),
DatabaseStatus (DatabaseStatus_Restoring, DatabaseStatus_Complete),
ListDatabasesResult (listDatabasesResult_databases),
PosixEpochTime,
Repo (Repo),
Expand All @@ -141,7 +141,9 @@ import Model.Command (
Command (..),
ShardingAssignmentChange (ShardAdded, ShardRemoved),
commandType,
defDependency,
defMeta,
defMetaWithDependency,
fixCreationTimes,
good,
insertTimeLapses,
Expand Down Expand Up @@ -194,6 +196,8 @@ main = do
, TestLabel "Mock site" $ TestCase mockSiteTest
, TestLabel "Backup restore" $ TestCase backupRestoreTest
, TestLabel "Open DB" $ TestCase openTest
, TestLabel "Backup restore dependency"
$ TestCase backupRestoreDependencyTest
]
]

Expand Down Expand Up @@ -532,3 +536,37 @@ openTest = withSystemTempDirectory "backupdir" $ \backupDir -> do
Env{..} -> do
openDBs <- readTVarIO envActive
HM.keys openDBs @?= [r]

backupRestoreDependencyTest :: IO ()
backupRestoreDependencyTest =
withSystemTempDirectory "backupdir" $ \backupDir -> do
dbConf <- dbConfig
withTEnv backupDir (dbConf backupDir) $ \TEnv {..} -> do
let
r1 = Repo "repo" "1"
r2 = Repo "repo" "2"
d2 = Repo "dep_repo" "2"
m1 = defMetaWithDependency $ Just $ defDependency "dep_repo" "1"
m2 = defMetaWithDependency $ Just $ defDependency "dep_repo" "2"
w1 <- mutateSystem tEnv (NewRemoteDB r1 m1)
w2 <- mutateSystem tEnv (NewRemoteDB r2 m2)
w3 <- mutateSystem tEnv (NewRemoteDB d2 defMeta)
w4 <- mutateSystem tEnv (ShardingAssignmentChange $ ShardAdded "1")
w5 <- mutateSystem tEnv (ShardingAssignmentChange $ ShardAdded "2")

runDatabaseJanitor (mockedEnv tEnv)
w6 <- wait $ w1 <> w2 <> w3 <> w4 <> w5
w7 <- mutateSystem tEnv DBDownloaded
w8 <- mutateSystem tEnv DBDownloaded
waitAll $ w6 <> w7 <> w8
dbs2 <-
listDatabasesResult_databases
<$> listDatabases (mockedEnv tEnv) def
logInfo $ show dbs2
dbs <-
filter hereDBs . listDatabasesResult_databases
<$> listDatabases (mockedEnv tEnv) def
map database_repo dbs @?= [d2, r2]
where
hereDBs Glean.Types.Database {..} =
database_status == DatabaseStatus_Complete

0 comments on commit b764242

Please sign in to comment.