started on sim file parser

This commit is contained in:
Joey Hess 2024-09-11 11:53:25 -04:00
parent c4609a73f2
commit 84bbbeae9d
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
5 changed files with 116 additions and 12 deletions

View file

@ -36,7 +36,6 @@ import Logs.Location
import qualified Annex import qualified Annex
import qualified Remote import qualified Remote
import qualified Git.Construct import qualified Git.Construct
import qualified Git.Remote.Remove
import qualified Annex.Queue import qualified Annex.Queue
import System.Random import System.Random
@ -161,7 +160,7 @@ data SimCommand
| CommandConnect RepoName RemoteName | CommandConnect RepoName RemoteName
| CommandDisconnect RepoName RemoteName | CommandDisconnect RepoName RemoteName
| CommandAddTree RepoName PreferredContentExpression | CommandAddTree RepoName PreferredContentExpression
| CommandAdd RawFilePath ByteSize RepoName | CommandAdd RawFilePath ByteSize [RepoName]
| CommandStep Int | CommandStep Int
| CommandAction RepoName SimAction | CommandAction RepoName SimAction
| CommandSeed Int | CommandSeed Int
@ -177,6 +176,8 @@ data SimCommand
| CommandGroupWanted Group PreferredContentExpression | CommandGroupWanted Group PreferredContentExpression
| CommandMaxSize RepoName MaxSize | CommandMaxSize RepoName MaxSize
| CommandRebalance Bool | CommandRebalance Bool
| CommandComment String
| CommandBlank
deriving (Show) deriving (Show)
data SimAction data SimAction
@ -207,11 +208,11 @@ applySimCommand
:: SimCommand :: SimCommand
-> SimState -> SimState
-> Either String (Either (Annex SimState) SimState) -> Either String (Either (Annex SimState) SimState)
applySimCommand c st = applySimCommand cmd st =
applySimCommand' c $ flip addHistory c $ st applySimCommand' cmd $ flip addHistory cmd $ st
{ simVectorClock = { simVectorClock =
let (VectorClock c) = simVectorClock st let (VectorClock clk) = simVectorClock st
in VectorClock (succ c) in VectorClock (succ clk)
} }
applySimCommand' applySimCommand'
@ -253,11 +254,16 @@ applySimCommand' (CommandAddTree repo expr) st =
checkKnownRepo repo st $ const $ checkKnownRepo repo st $ const $
checkValidPreferredContentExpression expr $ Left $ checkValidPreferredContentExpression expr $ Left $
error "TODO" -- XXX error "TODO" -- XXX
applySimCommand' (CommandAdd file sz repo) st = checkKnownRepo repo st $ \u -> applySimCommand' (CommandAdd file sz repos) st =
let (k, st') = genSimKey sz st let (k, st') = genSimKey sz st
in Right $ Right $ setPresentKey u k repo $ st' in go k st' repos
{ simFiles = M.insert file k (simFiles st') where
} go k st' [] = Right $ Right st
go k st' (repo:rest) = checkKnownRepo repo st' $ \u ->
let st'' = setPresentKey u k repo $ st'
{ simFiles = M.insert file k (simFiles st')
}
in go k st'' rest
applySimCommand' (CommandStep _) _ = error "applySimCommand' CommandStep" applySimCommand' (CommandStep _) _ = error "applySimCommand' CommandStep"
applySimCommand' (CommandAction repo act) st = applySimCommand' (CommandAction repo act) st =
checkKnownRepo repo st $ \u -> checkKnownRepo repo st $ \u ->
@ -335,6 +341,8 @@ applySimCommand' (CommandMaxSize repo sz) st = checkKnownRepo repo st $ \u ->
applySimCommand' (CommandRebalance b) st = Right $ Right $ st applySimCommand' (CommandRebalance b) st = Right $ Right $ st
{ simRebalance = b { simRebalance = b
} }
applySimCommand' (CommandComment _) st = Right $ Right st
applySimCommand' CommandBlank st = Right $ Right st
applySimAction applySimAction
:: RepoName :: RepoName

94
Annex/Sim/File.hs Normal file
View file

@ -0,0 +1,94 @@
{- sim files
-
- Copyright 2024 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Annex.Sim.File where
import Annex.Sim
import Annex.Common
import Utility.DataUnits
import Data.Char
import Text.Read
parseSimFile :: String -> Either String [SimCommand]
parseSimFile = go [] . lines
where
go c [] = Right c
go c (l:ls) = case parseSimFileLine l of
Right cs -> go (c ++ cs) ls
Left err -> Left err
parseSimFileLine :: String -> Either String [SimCommand]
parseSimFileLine s
| "#" `isPrefixOf` s = Right [CommandComment s]
| all isSpace s = Right [CommandBlank]
| otherwise = case words s of
("init":name:[]) ->
Right [CommandInit (RepoName name)]
("initremote":name:[]) ->
Right [CommandInitRemote (RepoName name)]
("use":name:rest) ->
Right [CommandUse (RepoName name) (unwords rest)]
("connect":rest) ->
parseConnect CommandConnect rest
("disconnect":rest) ->
parseConnect CommandDisconnect rest
("addtree":name:rest) ->
Right [CommandAddTree(RepoName name) (unwords rest)]
("add":filename:size:repos) ->
case readSize dataUnits size of
Just sz -> Right [CommandAdd (toRawFilePath filename) sz (map RepoName repos)]
Nothing -> Left $ "Unable to parse file size \"" ++ size ++ "\""
("step":n:[]) ->
case readMaybe n of
Just n' -> Right [CommandStep n']
Nothing -> Left $ "Unable to parse step value \"" ++ n ++ "\""
("action":repo:"pull":remote:[]) ->
Right [CommandAction (RepoName repo) (ActionPull (RemoteName remote))]
("action":repo:"push":remote:[]) ->
Right [CommandAction (RepoName repo) (ActionPush (RemoteName remote))]
("action":repo:"getwanted":remote:[]) ->
Right [CommandAction (RepoName repo) (ActionGetWanted (RemoteName remote))]
("action":repo:"dropunwanted":[]) ->
Right [CommandAction (RepoName repo) (ActionDropUnwanted Nothing)]
("action":repo:"dropunwanted":remote:[]) ->
Right [CommandAction (RepoName repo) (ActionDropUnwanted (Just (RemoteName remote)))]
("action":repo:"gitpush":remote:[]) ->
Right [CommandAction (RepoName repo) (ActionGitPush (RemoteName remote))]
("action":repo:"gitpull":remote:[]) ->
Right [CommandAction (RepoName repo) (ActionGitPull (RemoteName remote))]
("seed":n:[]) ->
case readMaybe n of
Just n' -> Right [CommandSeed n']
Nothing -> Left $ "Unable to parse seed value \"" ++ n ++ "\""
("present":repo:file:[]) ->
Right [CommandPresent (RepoName repo) (toRawFilePath file)]
("notpresent":repo:file:[]) ->
Right [CommandNotPresent (RepoName repo) (toRawFilePath file)]
-- TODO rest
_ -> Left $ "Unable to parse sim file line: \"" ++ s ++ "\""
parseConnect :: (RepoName -> RemoteName -> SimCommand) -> [String] -> Either String [SimCommand]
parseConnect mk = go []
where
go c [] = Right c
go c (r1:"->":r2:rest) =
go (mk (RepoName r1) (RemoteName r2):c)
(chain r2 rest)
go c (r1:"<-":r2:rest) =
go (mk (RepoName r2) (RemoteName r1):c)
(chain r2 rest)
go c (r1:"<->":r2:rest) =
go (mk (RepoName r2) (RemoteName r1)
: mk (RepoName r1) (RemoteName r2)
: c
)
(chain r2 rest)
go _ rest = Left $ "Bad connect syntax near \"" ++ unwords rest ++ "\""
chain v rest = if null rest then rest else v:rest

View file

@ -11,6 +11,7 @@ module Command.Sim where
import Command import Command
import Annex.Sim import Annex.Sim
import Annex.Sim.File
import Utility.Tmp.Dir import Utility.Tmp.Dir
import System.Random import System.Random
@ -32,7 +33,7 @@ seek _ = do
>>= runSimCommand (CommandUse (RepoName "bar") "here") >>= runSimCommand (CommandUse (RepoName "bar") "here")
>>= runSimCommand (CommandConnect (RepoName "foo") (RemoteName "bar")) >>= runSimCommand (CommandConnect (RepoName "foo") (RemoteName "bar"))
>>= runSimCommand (CommandConnect (RepoName "bar") (RemoteName "foo")) >>= runSimCommand (CommandConnect (RepoName "bar") (RemoteName "foo"))
>>= runSimCommand (CommandAdd "bigfile" 1000000 (RepoName "foo")) >>= runSimCommand (CommandAdd "bigfile" 1000000 [RepoName "foo"])
>>= runSimCommand (CommandAction (RepoName "bar") (ActionGitPull (RemoteName "foo"))) >>= runSimCommand (CommandAction (RepoName "bar") (ActionGitPull (RemoteName "foo")))
>>= runSimCommand (CommandAction (RepoName "bar") (ActionGetWanted (RemoteName "foo"))) >>= runSimCommand (CommandAction (RepoName "bar") (ActionGetWanted (RemoteName "foo")))
st'' <- liftIO $ updateSimRepos st' st'' <- liftIO $ updateSimRepos st'

View file

@ -167,7 +167,7 @@ as passed to "git annex sim" while a simulation is running.
Simulate the equivilant of [[git-annex-pull]](1). Simulate the equivilant of [[git-annex-pull]](1).
* `action repo pull remote` * `action repo push remote`
Simulate the equivilant of [[git-annex-push]](1). Simulate the equivilant of [[git-annex-push]](1).

View file

@ -578,6 +578,7 @@ Executable git-annex
Annex.RepoSize.LiveUpdate Annex.RepoSize.LiveUpdate
Annex.SafeDropProof Annex.SafeDropProof
Annex.Sim Annex.Sim
Annex.Sim.File
Annex.SpecialRemote Annex.SpecialRemote
Annex.SpecialRemote.Config Annex.SpecialRemote.Config
Annex.Ssh Annex.Ssh