add action command to git-annex sim
step just picks a random action, and this allows finer control over what happens in the sim
This commit is contained in:
parent
21da5aadec
commit
64466d8687
3 changed files with 100 additions and 24 deletions
76
Annex/Sim.hs
76
Annex/Sim.hs
|
@ -16,7 +16,6 @@ import Types.Group
|
||||||
import Types.StandardGroups
|
import Types.StandardGroups
|
||||||
import Types.TrustLevel
|
import Types.TrustLevel
|
||||||
import Types.Difference
|
import Types.Difference
|
||||||
import Git.Types
|
|
||||||
import Git
|
import Git
|
||||||
import Backend.Hash (genTestKey)
|
import Backend.Hash (genTestKey)
|
||||||
import Annex.UUID
|
import Annex.UUID
|
||||||
|
@ -50,17 +49,11 @@ import qualified Data.UUID.V5 as U5
|
||||||
import qualified Utility.RawFilePath as R
|
import qualified Utility.RawFilePath as R
|
||||||
import qualified System.FilePath.ByteString as P
|
import qualified System.FilePath.ByteString as P
|
||||||
|
|
||||||
-- 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
|
data SimState = SimState
|
||||||
{ simRepos :: M.Map RepoName UUID
|
{ simRepos :: M.Map RepoName UUID
|
||||||
|
, simRepoList :: [RepoName]
|
||||||
, simRepoState :: M.Map RepoName SimRepoState
|
, simRepoState :: M.Map RepoName SimRepoState
|
||||||
, simConnections :: M.Map RepoName (S.Set RepoName)
|
, simConnections :: M.Map RepoName (S.Set RemoteName)
|
||||||
, simFiles :: M.Map RawFilePath Key
|
, simFiles :: M.Map RawFilePath Key
|
||||||
, simRng :: StdGen
|
, simRng :: StdGen
|
||||||
, simTrustLevels :: M.Map UUID TrustLevel
|
, simTrustLevels :: M.Map UUID TrustLevel
|
||||||
|
@ -73,12 +66,14 @@ data SimState = SimState
|
||||||
, simMaxSize :: M.Map UUID MaxSize
|
, simMaxSize :: M.Map UUID MaxSize
|
||||||
, simRebalance :: Bool
|
, simRebalance :: Bool
|
||||||
, simGetExistingRepoByName :: GetExistingRepoByName
|
, simGetExistingRepoByName :: GetExistingRepoByName
|
||||||
|
, simHistory :: [SimCommand]
|
||||||
}
|
}
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
emptySimState :: StdGen -> GetExistingRepoByName -> SimState
|
emptySimState :: StdGen -> GetExistingRepoByName -> SimState
|
||||||
emptySimState rng repobyname = SimState
|
emptySimState rng repobyname = SimState
|
||||||
{ simRepos = mempty
|
{ simRepos = mempty
|
||||||
|
, simRepoList = mempty
|
||||||
, simRepoState = mempty
|
, simRepoState = mempty
|
||||||
, simConnections = mempty
|
, simConnections = mempty
|
||||||
, simFiles = mempty
|
, simFiles = mempty
|
||||||
|
@ -93,6 +88,7 @@ emptySimState rng repobyname = SimState
|
||||||
, simMaxSize = mempty
|
, simMaxSize = mempty
|
||||||
, simRebalance = False
|
, simRebalance = False
|
||||||
, simGetExistingRepoByName = repobyname
|
, simGetExistingRepoByName = repobyname
|
||||||
|
, simHistory = []
|
||||||
}
|
}
|
||||||
|
|
||||||
-- State that can vary between different repos in the simulation.
|
-- State that can vary between different repos in the simulation.
|
||||||
|
@ -114,15 +110,19 @@ setPresentKey u k rst = rst
|
||||||
newtype RepoName = RepoName { fromRepoName :: String }
|
newtype RepoName = RepoName { fromRepoName :: String }
|
||||||
deriving (Show, Eq, Ord)
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
|
newtype RemoteName = RemoteName { fromRemoteName :: String }
|
||||||
|
deriving (Show, Eq, Ord)
|
||||||
|
|
||||||
data SimCommand
|
data SimCommand
|
||||||
= CommandInit RepoName
|
= CommandInit RepoName
|
||||||
| CommandInitRemote RepoName
|
| CommandInitRemote RepoName
|
||||||
| CommandUse RepoName String
|
| CommandUse RepoName String
|
||||||
| CommandConnect RepoName RepoName
|
| CommandConnect RepoName RemoteName
|
||||||
| CommandDisconnect RepoName RepoName
|
| CommandDisconnect RepoName RemoteName
|
||||||
| CommandAddTree RepoName PreferredContentExpression
|
| CommandAddTree RepoName PreferredContentExpression
|
||||||
| CommandAdd FilePath ByteSize RepoName
|
| CommandAdd FilePath ByteSize RepoName
|
||||||
| CommandStep Int
|
| CommandStep Int
|
||||||
|
| CommandAction RepoName SimAction
|
||||||
| CommandSeed Int
|
| CommandSeed Int
|
||||||
| CommandPresent RepoName FilePath
|
| CommandPresent RepoName FilePath
|
||||||
| CommandNotPresent RepoName FilePath
|
| CommandNotPresent RepoName FilePath
|
||||||
|
@ -138,6 +138,16 @@ data SimCommand
|
||||||
| CommandRebalance Bool
|
| CommandRebalance Bool
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
|
data SimAction
|
||||||
|
= ActionPull RemoteName
|
||||||
|
| ActionPush RemoteName
|
||||||
|
| ActionGetWanted RemoteName
|
||||||
|
| ActionDropUnwanted (Maybe RemoteName)
|
||||||
|
| ActionSendWanted RemoteName
|
||||||
|
| ActionGitPush RemoteName
|
||||||
|
| ActionGitPull RemoteName
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
runSimCommand :: SimCommand -> SimState -> Annex SimState
|
runSimCommand :: SimCommand -> SimState -> Annex SimState
|
||||||
runSimCommand cmd st = case applySimCommand cmd st of
|
runSimCommand cmd st = case applySimCommand cmd st of
|
||||||
Left err -> giveup err
|
Left err -> giveup err
|
||||||
|
@ -164,7 +174,7 @@ applySimCommand (CommandUse reponame s) st =
|
||||||
++ fromRepoName reponame
|
++ fromRepoName reponame
|
||||||
++ "\" in the simulation because " ++ msg
|
++ "\" in the simulation because " ++ msg
|
||||||
applySimCommand (CommandConnect repo remote) st =
|
applySimCommand (CommandConnect repo remote) st =
|
||||||
checkKnownRepo repo st $ const $ checkKnownRepo remote st $ const $ Right $ Right $ st
|
checkKnownRepo repo st $ const $ Right $ Right $ st
|
||||||
{ simConnections =
|
{ simConnections =
|
||||||
let s = case M.lookup repo (simConnections st) of
|
let s = case M.lookup repo (simConnections st) of
|
||||||
Just cs -> S.insert remote cs
|
Just cs -> S.insert remote cs
|
||||||
|
@ -172,7 +182,7 @@ applySimCommand (CommandConnect repo remote) st =
|
||||||
in M.insert repo s (simConnections st)
|
in M.insert repo s (simConnections st)
|
||||||
}
|
}
|
||||||
applySimCommand (CommandDisconnect repo remote) st =
|
applySimCommand (CommandDisconnect repo remote) st =
|
||||||
checkKnownRepo repo st $ const $ checkKnownRepo remote st $ const $ Right $ Right $ st
|
checkKnownRepo repo st $ const $ Right $ Right $ st
|
||||||
{ simConnections =
|
{ simConnections =
|
||||||
let sc = case M.lookup repo (simConnections st) of
|
let sc = case M.lookup repo (simConnections st) of
|
||||||
Just s -> S.delete remote s
|
Just s -> S.delete remote s
|
||||||
|
@ -194,10 +204,31 @@ applySimCommand (CommandAdd file sz repo) st = checkKnownRepo repo st $ \u ->
|
||||||
Nothing -> error "no simRepoState in applySimCommand CommandAdd"
|
Nothing -> error "no simRepoState in applySimCommand CommandAdd"
|
||||||
}
|
}
|
||||||
applySimCommand (CommandStep n) st
|
applySimCommand (CommandStep n) st
|
||||||
| n > 0 = applySimCommand
|
| n > 0 = undefined -- XXX TODO
|
||||||
(CommandStep (pred n))
|
{-
|
||||||
(fst $ stepSimulation st)
|
let (repo, st') = randomRepo st
|
||||||
|
(act, st'') = randomAction st'
|
||||||
|
st''' = applySimCommand (CommandAction repo act) st''
|
||||||
|
st'''' = st''' { simHistory = act : simHistory st''' }
|
||||||
|
in applySimCommand (CommandStep (pred n)) st''''
|
||||||
|
-}
|
||||||
| otherwise = Right $ Right st
|
| otherwise = Right $ Right st
|
||||||
|
applySimCommand (CommandAction repo (ActionPull remote)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionPush remote)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionGetWanted remote)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionDropUnwanted Nothing)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionDropUnwanted (Just remote))) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionSendWanted remote)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionGitPush remote)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
|
applySimCommand (CommandAction repo (ActionGitPull remote)) st =
|
||||||
|
checkKnownRepo repo st $ \u -> undefined -- XXX TODO
|
||||||
applySimCommand (CommandSeed rngseed) st = Right $ Right $ st
|
applySimCommand (CommandSeed rngseed) st = Right $ Right $ st
|
||||||
{ simRng = mkStdGen rngseed
|
{ simRng = mkStdGen rngseed
|
||||||
}
|
}
|
||||||
|
@ -291,6 +322,16 @@ simRandom st mk f =
|
||||||
let (v, rng) = mk (simRng st)
|
let (v, rng) = mk (simRng st)
|
||||||
in (f v, st { simRng = rng })
|
in (f v, st { simRng = rng })
|
||||||
|
|
||||||
|
randomRepo :: SimState -> (Maybe RepoName, SimState)
|
||||||
|
randomRepo st
|
||||||
|
| null (simRepoList st) = (Nothing, st)
|
||||||
|
| otherwise = simRandom st
|
||||||
|
(randomR (0, length (simRepoList st) - 1))
|
||||||
|
(\n -> Just $ simRepoList st !! n)
|
||||||
|
|
||||||
|
randomAction :: SimState -> (SimAction, SimState)
|
||||||
|
randomAction = undefined -- XXX TODO
|
||||||
|
|
||||||
randomWords :: Int -> StdGen -> ([Word8], StdGen)
|
randomWords :: Int -> StdGen -> ([Word8], StdGen)
|
||||||
randomWords = go []
|
randomWords = go []
|
||||||
where
|
where
|
||||||
|
@ -349,6 +390,9 @@ newSimRepoConfig u isspecialremote = SimRepoConfig
|
||||||
addRepo :: RepoName -> SimRepoConfig -> SimState -> SimState
|
addRepo :: RepoName -> SimRepoConfig -> SimState -> SimState
|
||||||
addRepo reponame simrepo st = st
|
addRepo reponame simrepo st = st
|
||||||
{ simRepos = M.insert reponame u (simRepos st)
|
{ simRepos = M.insert reponame u (simRepos st)
|
||||||
|
, simRepoList = if reponame `elem` simRepoList st
|
||||||
|
then simRepoList st
|
||||||
|
else reponame : simRepoList st
|
||||||
, simRepoState = M.insert reponame rst (simRepoState st)
|
, simRepoState = M.insert reponame rst (simRepoState st)
|
||||||
, simConnections = M.insert reponame mempty (simConnections st)
|
, simConnections = M.insert reponame mempty (simConnections st)
|
||||||
, simGroups = M.insert u (simRepoGroups simrepo) (simGroups st)
|
, simGroups = M.insert u (simRepoGroups simrepo) (simGroups st)
|
||||||
|
|
|
@ -29,7 +29,7 @@ seek _ = do
|
||||||
st' <- runSimCommand (CommandInit (RepoName "foo")) st
|
st' <- runSimCommand (CommandInit (RepoName "foo")) st
|
||||||
>>= runSimCommand (CommandTrustLevel (RepoName "foo") "trusted")
|
>>= runSimCommand (CommandTrustLevel (RepoName "foo") "trusted")
|
||||||
>>= runSimCommand (CommandUse (RepoName "bar") "here")
|
>>= runSimCommand (CommandUse (RepoName "bar") "here")
|
||||||
>>= runSimCommand (CommandConnect (RepoName "foo") (RepoName "bar"))
|
>>= runSimCommand (CommandConnect (RepoName "foo") (RemoteName "bar"))
|
||||||
>>= runSimCommand (CommandAdd "foo" 100000 (RepoName "foo"))
|
>>= runSimCommand (CommandAdd "foo" 100000 (RepoName "foo"))
|
||||||
let simdir = \u -> tmpdir </> fromUUID u
|
let simdir = \u -> tmpdir </> fromUUID u
|
||||||
st'' <- liftIO $ updateSimRepos r simdir st'
|
st'' <- liftIO $ updateSimRepos r simdir st'
|
||||||
|
|
|
@ -25,16 +25,11 @@ with the command in the same format used in the sim file (see sim commands
|
||||||
list below). For example, "git annex sim step 1" runs the simulation one step.
|
list below). For example, "git annex sim step 1" runs the simulation one step.
|
||||||
|
|
||||||
The simulation writes to an output sim file as it runs, which contains the
|
The simulation writes to an output sim file as it runs, which contains the
|
||||||
entire simulation input, as well as the results of the simulation.
|
entire simulation input, as well as the actions performed in the
|
||||||
|
simulation, and the results of the simulation.
|
||||||
This allows re-running the same simulation later, as well as analyzing
|
This allows re-running the same simulation later, as well as analyzing
|
||||||
the results of the simulation.
|
the results of the simulation.
|
||||||
|
|
||||||
On each step of the simulation, a simulated repository is selected,
|
|
||||||
and an action is performed in it. The actions include pushing and pulling
|
|
||||||
the git-annex branch to and from remotes of the simulated repository, and
|
|
||||||
simulating the transfer of annexed files to and from remotes according to
|
|
||||||
the configuration.
|
|
||||||
|
|
||||||
While a simulation is running, the command "git annex visit repo", where
|
While a simulation is running, the command "git annex visit repo", where
|
||||||
"repo" is the name of one of the repositories in the simulation, will spawn
|
"repo" is the name of one of the repositories in the simulation, will spawn
|
||||||
a subshell in a git repository whose git-annex branch contains the state of
|
a subshell in a git repository whose git-annex branch contains the state of
|
||||||
|
@ -165,6 +160,43 @@ as passed to "git annex sim" while a simulation is running.
|
||||||
|
|
||||||
Run the simulation forward by this many steps.
|
Run the simulation forward by this many steps.
|
||||||
|
|
||||||
|
On each step of the simulation, a simulated repository is selected
|
||||||
|
at random, and a random action is performed in it.
|
||||||
|
|
||||||
|
* `action repo pull remote`
|
||||||
|
|
||||||
|
Simulate the equivilant of [[git-annex-pull]](1).
|
||||||
|
|
||||||
|
* `action repo pull remote`
|
||||||
|
|
||||||
|
Simulate the equivilant of [[git-annex-push]](1).
|
||||||
|
|
||||||
|
* `action repo getwanted remote`
|
||||||
|
|
||||||
|
Simulate the repository getting files it wants from the remote.
|
||||||
|
|
||||||
|
* `action repo dropunwanted`
|
||||||
|
|
||||||
|
Simulate the repository dropping files it does not want,
|
||||||
|
when it is able to verify enough copies exist on remotes.
|
||||||
|
|
||||||
|
* `action repo dropunwanted remote`
|
||||||
|
|
||||||
|
Simulate the repository dropping files from the remote that the remote
|
||||||
|
does not want, when it is able to verify enouh copies exist.
|
||||||
|
|
||||||
|
* `action repo sendwanted remote`
|
||||||
|
|
||||||
|
Simulate the repository sending files that the remote wants to it.
|
||||||
|
|
||||||
|
* `action repo gitpush remote`
|
||||||
|
|
||||||
|
Simulate the repository pushing the git-annex branch to the remote.
|
||||||
|
|
||||||
|
* `action repo gitpull remote`
|
||||||
|
|
||||||
|
Simulate the repository pulling the git-annex branch from the remote.
|
||||||
|
|
||||||
* `seed N`
|
* `seed N`
|
||||||
|
|
||||||
Sets the random seed to a given number. Using this should make the
|
Sets the random seed to a given number. Using this should make the
|
||||||
|
|
Loading…
Reference in a new issue