2024-09-04 19:10:39 +00:00
|
|
|
{- git-annex simulator
|
|
|
|
-
|
|
|
|
- Copyright 2024 Joey Hess <id@joeyh.name>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
|
|
|
module Annex.Sim where
|
|
|
|
|
|
|
|
import Utility.DataUnits
|
|
|
|
import Types.NumCopies
|
|
|
|
import Types.RepoSize
|
|
|
|
import Types.Key
|
|
|
|
import Types.UUID
|
2024-09-05 19:22:41 +00:00
|
|
|
import Types.StandardGroups
|
2024-09-04 19:10:39 +00:00
|
|
|
import Annex (Annex)
|
|
|
|
import Backend.Hash (genTestKey)
|
|
|
|
import Annex.UUID
|
2024-09-05 19:22:41 +00:00
|
|
|
import Annex.FileMatcher
|
2024-09-04 19:10:39 +00:00
|
|
|
import Utility.FileSystemEncoding
|
2024-09-05 14:50:04 +00:00
|
|
|
import qualified Remote
|
2024-09-04 19:10:39 +00:00
|
|
|
|
|
|
|
import System.Random
|
|
|
|
import Data.Word
|
|
|
|
import Data.Maybe
|
|
|
|
import qualified Data.Map.Strict as M
|
|
|
|
import qualified Data.Set as S
|
|
|
|
import qualified Data.ByteString as B
|
|
|
|
import qualified Data.ByteString.Lazy as L
|
|
|
|
import qualified Data.UUID as U
|
|
|
|
import qualified Data.UUID.V5 as U5
|
|
|
|
|
|
|
|
-- Runs the simulation one step. As well as the updated SimState,
|
|
|
|
-- returns SimCommands for every change that the simulation made.
|
|
|
|
-- Eg, CommandPresent is returned when a file's content is added to a repo,
|
|
|
|
-- and CommandNotPresent when a file's content is dropped.
|
|
|
|
stepSimulation :: SimState -> (SimState, [SimCommand])
|
|
|
|
stepSimulation st = undefined -- XXX TODO
|
|
|
|
|
|
|
|
data SimState = SimState
|
|
|
|
{ simRepos :: M.Map RepoName UUID
|
|
|
|
, simRepoState :: M.Map RepoName SimRepoState
|
|
|
|
, simSpecialRemotes :: M.Map RepoName UUID
|
|
|
|
, simConnections :: M.Map RepoName (S.Set RepoName)
|
|
|
|
, simFiles :: M.Map FilePath Key
|
|
|
|
, simRng :: StdGen
|
|
|
|
, simNumCopies :: NumCopies
|
|
|
|
, simGroups :: M.Map RepoName (S.Set GroupName)
|
2024-09-05 19:22:41 +00:00
|
|
|
, simWanted :: M.Map RepoName PreferredContentExpression
|
|
|
|
, simRequired :: M.Map RepoName PreferredContentExpression
|
|
|
|
, simGroupWanted :: M.Map GroupName PreferredContentExpression
|
2024-09-04 19:10:39 +00:00
|
|
|
, simMaxSize :: M.Map RepoName MaxSize
|
|
|
|
, simRebalance :: Bool
|
2024-09-05 14:50:04 +00:00
|
|
|
, simExistingRepoByName :: ExistingRepoByName
|
2024-09-04 19:10:39 +00:00
|
|
|
}
|
|
|
|
deriving (Show)
|
|
|
|
|
2024-09-05 14:50:04 +00:00
|
|
|
emptySimState :: Int -> ExistingRepoByName -> SimState
|
|
|
|
emptySimState rngseed repobyname = SimState
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simRepos = mempty
|
|
|
|
, simSpecialRemotes = mempty
|
|
|
|
, simRepoState = mempty
|
|
|
|
, simConnections = mempty
|
|
|
|
, simFiles = mempty
|
|
|
|
, simRng = mkStdGen rngseed
|
|
|
|
, simNumCopies = configuredNumCopies 1
|
|
|
|
, simGroups = mempty
|
|
|
|
, simWanted = mempty
|
|
|
|
, simRequired = mempty
|
|
|
|
, simGroupWanted = mempty
|
|
|
|
, simMaxSize = mempty
|
|
|
|
, simRebalance = False
|
2024-09-05 14:50:04 +00:00
|
|
|
, simExistingRepoByName = repobyname
|
2024-09-04 19:10:39 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
-- State that can vary between different repos in the simulation.
|
|
|
|
data SimRepoState = SimRepoState
|
|
|
|
{ simLocations :: M.Map Key (S.Set RepoName)
|
|
|
|
}
|
|
|
|
deriving (Show, Eq)
|
|
|
|
|
|
|
|
emptySimRepoState :: SimRepoState
|
|
|
|
emptySimRepoState = SimRepoState mempty
|
|
|
|
|
|
|
|
setPresentKey :: RepoName -> Key -> SimRepoState -> SimRepoState
|
|
|
|
setPresentKey repo k rst = rst
|
|
|
|
{ simLocations =
|
|
|
|
M.insertWith S.union k (S.singleton repo) (simLocations rst)
|
|
|
|
}
|
|
|
|
|
|
|
|
newtype RepoName = RepoName { fromRepoName :: String }
|
|
|
|
deriving (Show, Eq, Ord)
|
|
|
|
|
|
|
|
newtype GroupName = GroupName { fromGroupName :: String }
|
|
|
|
deriving (Show, Eq, Ord)
|
|
|
|
|
|
|
|
data SimCommand
|
|
|
|
= CommandInit RepoName
|
|
|
|
| CommandInitRemote RepoName
|
|
|
|
| CommandUse RepoName String
|
|
|
|
| CommandConnect RepoName RepoName
|
|
|
|
| CommandDisconnect RepoName RepoName
|
2024-09-05 19:22:41 +00:00
|
|
|
| CommandAddTree RepoName PreferredContentExpression
|
2024-09-04 19:10:39 +00:00
|
|
|
| CommandAdd FilePath ByteSize RepoName
|
|
|
|
| CommandStep Int
|
|
|
|
| CommandSeed Int
|
|
|
|
| CommandPresent RepoName FilePath
|
|
|
|
| CommandNotPresent RepoName FilePath
|
|
|
|
| CommandNumCopies Int
|
|
|
|
| CommandGroup RepoName GroupName
|
|
|
|
| CommandUngroup RepoName GroupName
|
2024-09-05 19:22:41 +00:00
|
|
|
| CommandWanted RepoName PreferredContentExpression
|
|
|
|
| CommandRequired RepoName PreferredContentExpression
|
|
|
|
| CommandGroupWanted GroupName PreferredContentExpression
|
2024-09-04 19:10:39 +00:00
|
|
|
| CommandMaxSize RepoName MaxSize
|
|
|
|
| CommandRebalance Bool
|
|
|
|
deriving (Show)
|
|
|
|
|
2024-09-05 19:22:41 +00:00
|
|
|
applySimCommand
|
|
|
|
:: SimCommand
|
|
|
|
-> SimState
|
|
|
|
-> Either String (Either (Annex SimState) SimState)
|
2024-09-04 19:10:39 +00:00
|
|
|
applySimCommand (CommandInit reponame) st =
|
|
|
|
let (u, st') = genSimUUID st reponame
|
2024-09-05 19:22:41 +00:00
|
|
|
in Right $ Right $ st'
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simRepos = M.insert reponame u (simRepos st')
|
|
|
|
}
|
|
|
|
applySimCommand (CommandInitRemote reponame) st =
|
|
|
|
let (u, st') = genSimUUID st reponame
|
2024-09-05 19:22:41 +00:00
|
|
|
in Right $ Right $ st'
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simSpecialRemotes = M.insert reponame u (simSpecialRemotes st')
|
|
|
|
}
|
2024-09-05 14:50:04 +00:00
|
|
|
applySimCommand (CommandUse reponame s) st =
|
2024-09-05 19:22:41 +00:00
|
|
|
case existingRepoByName (simExistingRepoByName st) s of
|
|
|
|
(u:[], _) -> Right $ Right $ st
|
2024-09-05 14:50:04 +00:00
|
|
|
{ simSpecialRemotes = M.insert reponame u (simSpecialRemotes st)
|
|
|
|
}
|
|
|
|
(_, msg) -> Left $ "Unable to use a repository \""
|
|
|
|
++ fromRepoName reponame
|
|
|
|
++ "\" in the simulation because " ++ msg
|
2024-09-05 19:22:41 +00:00
|
|
|
applySimCommand (CommandConnect repo remote) st =
|
|
|
|
checkKnownRepo repo st $ checkKnownRepo remote st $ Right $ Right $ st
|
|
|
|
{ simConnections =
|
|
|
|
let s = case M.lookup repo (simConnections st) of
|
|
|
|
Just cs -> S.insert remote cs
|
|
|
|
Nothing -> S.singleton remote
|
|
|
|
in M.insert repo s (simConnections st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandDisconnect repo remote) st =
|
|
|
|
checkKnownRepo repo st $ checkKnownRepo remote st $ Right $ Right $ st
|
|
|
|
{ simConnections =
|
|
|
|
let sc = case M.lookup repo (simConnections st) of
|
|
|
|
Just s -> S.delete remote s
|
|
|
|
Nothing -> S.empty
|
|
|
|
in M.insert repo sc (simConnections st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandAddTree repo expr) st =
|
|
|
|
checkKnownRepo repo st $
|
|
|
|
checkValidPreferredContentExpression expr $ Left $
|
|
|
|
error "TODO" -- XXX
|
|
|
|
applySimCommand (CommandAdd file sz repo) st = checkKnownRepo repo st $
|
2024-09-04 19:10:39 +00:00
|
|
|
let (k, st') = genSimKey sz st
|
2024-09-05 19:22:41 +00:00
|
|
|
in Right $ Right $ st'
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simFiles = M.insert file k (simFiles st')
|
|
|
|
, simRepoState =
|
|
|
|
let rst = fromMaybe emptySimRepoState $
|
|
|
|
M.lookup repo (simRepoState st')
|
|
|
|
rst' = setPresentKey repo k rst
|
|
|
|
in M.insert repo rst' (simRepoState st')
|
|
|
|
}
|
|
|
|
applySimCommand (CommandStep n) st
|
|
|
|
| n > 0 = applySimCommand
|
|
|
|
(CommandStep (pred n))
|
|
|
|
(fst $ stepSimulation st)
|
2024-09-05 19:22:41 +00:00
|
|
|
| otherwise = Right $ Right st
|
|
|
|
applySimCommand (CommandSeed rngseed) st = Right $ Right $ st
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simRng = mkStdGen rngseed
|
|
|
|
}
|
2024-09-05 19:22:41 +00:00
|
|
|
applySimCommand (CommandPresent repo file) st = checkKnownRepo repo st $
|
2024-09-04 19:10:39 +00:00
|
|
|
case (M.lookup file (simFiles st), M.lookup repo (simRepoState st)) of
|
|
|
|
(Just k, Just rst) -> case M.lookup k (simLocations rst) of
|
2024-09-05 19:22:41 +00:00
|
|
|
Just locs | S.member repo locs -> Right $ Right st
|
2024-09-04 19:10:39 +00:00
|
|
|
_ -> missing
|
2024-09-05 19:22:41 +00:00
|
|
|
(Just _, Nothing) -> missing
|
2024-09-04 19:10:39 +00:00
|
|
|
(Nothing, _) -> Left $ "Expected " ++ file
|
|
|
|
++ " to be present in " ++ fromRepoName repo
|
|
|
|
++ ", but the simulation does not include that file."
|
|
|
|
where
|
|
|
|
missing = Left $ "Expected " ++ file ++ " to be present in "
|
|
|
|
++ fromRepoName repo ++ ", but it is not."
|
2024-09-05 19:22:41 +00:00
|
|
|
applySimCommand (CommandNotPresent repo file) st = checkKnownRepo repo st $
|
2024-09-04 19:10:39 +00:00
|
|
|
case (M.lookup file (simFiles st), M.lookup repo (simRepoState st)) of
|
|
|
|
(Just k, Just rst) -> case M.lookup k (simLocations rst) of
|
2024-09-05 19:22:41 +00:00
|
|
|
Just locs | S.notMember repo locs -> Right $ Right st
|
2024-09-04 19:10:39 +00:00
|
|
|
_ -> present
|
2024-09-05 19:22:41 +00:00
|
|
|
(Just _, Nothing) -> present
|
2024-09-04 19:10:39 +00:00
|
|
|
(Nothing, _) -> Left $ "Expected " ++ file
|
|
|
|
++ " to not be present in " ++ fromRepoName repo
|
|
|
|
++ ", but the simulation does not include that file."
|
|
|
|
where
|
|
|
|
present = Left $ "Expected " ++ file ++ " not to be present in "
|
|
|
|
++ fromRepoName repo ++ ", but it is present."
|
2024-09-05 19:22:41 +00:00
|
|
|
applySimCommand (CommandNumCopies n) st = Right $ Right $ st
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simNumCopies = configuredNumCopies n
|
|
|
|
}
|
2024-09-05 19:22:41 +00:00
|
|
|
applySimCommand (CommandGroup repo group) st = checkKnownRepo repo st $
|
|
|
|
Right $ Right $ st
|
|
|
|
{ simGroups = M.insertWith S.union repo
|
|
|
|
(S.singleton group)
|
|
|
|
(simGroups st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandUngroup repo group) st = checkKnownRepo repo st $
|
|
|
|
Right $ Right $ st
|
|
|
|
{ simGroups = M.adjust (S.delete group) repo (simGroups st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandWanted repo expr) st = checkKnownRepo repo st $
|
|
|
|
checkValidPreferredContentExpression expr $ Right $ st
|
|
|
|
{ simWanted = M.insert repo expr (simWanted st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandRequired repo expr) st = checkKnownRepo repo st $
|
|
|
|
checkValidPreferredContentExpression expr $ Right $ st
|
|
|
|
{ simRequired = M.insert repo expr (simRequired st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandGroupWanted group expr) st =
|
|
|
|
checkValidPreferredContentExpression expr $ Right $ st
|
|
|
|
{ simGroupWanted = M.insert group expr (simGroupWanted st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandMaxSize repo sz) st = checkKnownRepo repo st $
|
|
|
|
Right $ Right $ st
|
|
|
|
{ simMaxSize = M.insert repo sz (simMaxSize st)
|
|
|
|
}
|
|
|
|
applySimCommand (CommandRebalance b) st = Right $ Right $ st
|
2024-09-04 19:10:39 +00:00
|
|
|
{ simRebalance = b
|
|
|
|
}
|
|
|
|
|
2024-09-05 19:22:41 +00:00
|
|
|
checkKnownRepo :: RepoName -> SimState -> Either String a -> Either String a
|
|
|
|
checkKnownRepo reponame st a = case M.lookup reponame (simRepos st) of
|
|
|
|
Just _ -> a
|
|
|
|
Nothing -> Left $ "No repository in the simulation is named \""
|
|
|
|
++ fromRepoName reponame ++ "\"."
|
|
|
|
|
|
|
|
checkValidPreferredContentExpression :: PreferredContentExpression -> v -> Either String v
|
|
|
|
checkValidPreferredContentExpression expr v =
|
|
|
|
case checkPreferredContentExpression expr of
|
|
|
|
Nothing -> Right v
|
|
|
|
Just e -> Left $ "Failed parsing \"" ++ expr ++ "\": " ++ e
|
|
|
|
|
2024-09-04 19:10:39 +00:00
|
|
|
simRandom :: SimState -> (StdGen -> (v, StdGen)) -> (v -> r) -> (r, SimState)
|
|
|
|
simRandom st mk f =
|
|
|
|
let (v, rng) = mk (simRng st)
|
|
|
|
in (f v, st { simRng = rng })
|
|
|
|
|
|
|
|
randomWords :: Int -> StdGen -> ([Word8], StdGen)
|
|
|
|
randomWords = go []
|
|
|
|
where
|
|
|
|
go c n g
|
|
|
|
| n < 1 = (c, g)
|
|
|
|
| otherwise =
|
|
|
|
let (w, g') = random g
|
|
|
|
in go (w:c) (pred n) g'
|
|
|
|
|
|
|
|
genSimKey :: ByteSize -> SimState -> (Key, SimState)
|
|
|
|
genSimKey sz st = simRandom st (randomWords 1024) mk
|
|
|
|
where
|
|
|
|
mk b =
|
|
|
|
let tk = genTestKey $ L.pack b
|
|
|
|
in alterKey tk $ \kd -> kd { keySize = Just sz }
|
|
|
|
|
|
|
|
genSimUUID :: SimState -> RepoName -> (UUID, SimState)
|
|
|
|
genSimUUID st (RepoName reponame) = simRandom st (randomWords 1024)
|
|
|
|
(\l -> genUUIDInNameSpace simUUIDNameSpace (encodeBS reponame <> B.pack l))
|
|
|
|
|
|
|
|
simUUIDNameSpace :: U.UUID
|
|
|
|
simUUIDNameSpace = U5.generateNamed U5.namespaceURL $
|
|
|
|
B.unpack "http://git-annex.branchable.com/git-annex-sim/"
|
2024-09-05 14:50:04 +00:00
|
|
|
|
|
|
|
newtype ExistingRepoByName = ExistingRepoByName
|
2024-09-05 19:22:41 +00:00
|
|
|
{ existingRepoByName :: String -> ([UUID], String)
|
2024-09-05 14:50:04 +00:00
|
|
|
}
|
|
|
|
|
|
|
|
instance Show ExistingRepoByName where
|
|
|
|
show _ = "ExistingRepoByName"
|
|
|
|
|
|
|
|
mkExistingRepoByName :: Annex ExistingRepoByName
|
2024-09-05 19:22:41 +00:00
|
|
|
mkExistingRepoByName = ExistingRepoByName <$> Remote.nameToUUID''
|