factor out a stopUnless

code melt for lunch
This commit is contained in:
Joey Hess 2011-12-09 12:23:45 -04:00
parent d64132a43a
commit 3f5f28b487
9 changed files with 69 additions and 107 deletions

View file

@ -10,6 +10,7 @@ module Command (
noRepo, noRepo,
next, next,
stop, stop,
stopUnless,
prepCommand, prepCommand,
doCommand, doCommand,
whenAnnexed, whenAnnexed,
@ -49,6 +50,12 @@ next a = return $ Just a
stop :: Annex (Maybe a) stop :: Annex (Maybe a)
stop = return Nothing stop = return Nothing
{- Stops unless a condition is met. -}
stopUnless :: Annex Bool -> Annex (Maybe a) -> Annex (Maybe a)
stopUnless c a = do
ok <- c
if ok then a else stop
{- Prepares to run a command via the check and seek stages, returning a {- Prepares to run a command via the check and seek stages, returning a
- list of actions to perform to run the command. -} - list of actions to perform to run the command. -}
prepCommand :: Command -> [String] -> Annex [CommandCleanup] prepCommand :: Command -> [String] -> Annex [CommandCleanup]

View file

@ -45,18 +45,15 @@ download url file = do
let dummykey = Backend.URL.fromUrl url let dummykey = Backend.URL.fromUrl url
tmp <- fromRepo $ gitAnnexTmpLocation dummykey tmp <- fromRepo $ gitAnnexTmpLocation dummykey
liftIO $ createDirectoryIfMissing True (parentDir tmp) liftIO $ createDirectoryIfMissing True (parentDir tmp)
ok <- liftIO $ Url.download url tmp stopUnless (liftIO $ Url.download url tmp) $ do
if ok [(backend, _)] <- Backend.chooseBackends [file]
then do k <- Backend.genKey tmp backend
[(backend, _)] <- Backend.chooseBackends [file] case k of
k <- Backend.genKey tmp backend Nothing -> stop
case k of Just (key, _) -> do
Nothing -> stop moveAnnex key tmp
Just (key, _) -> do setUrlPresent key url
moveAnnex key tmp next $ Command.Add.cleanup file key True
setUrlPresent key url
next $ Command.Add.cleanup file key True
else stop
nodownload :: String -> FilePath -> CommandPerform nodownload :: String -> FilePath -> CommandPerform
nodownload url file = do nodownload url file = do

View file

@ -37,13 +37,9 @@ start numcopies file (key, _) = autoCopies key (>) numcopies $ do
else startRemote file numcopies key remote else startRemote file numcopies key remote
startLocal :: FilePath -> Maybe Int -> Key -> CommandStart startLocal :: FilePath -> Maybe Int -> Key -> CommandStart
startLocal file numcopies key = do startLocal file numcopies key = stopUnless (inAnnex key) $ do
present <- inAnnex key showStart "drop" file
if present next $ performLocal key numcopies
then do
showStart "drop" file
next $ performLocal key numcopies
else stop
startRemote :: FilePath -> Maybe Int -> Key -> Remote.Remote Annex -> CommandStart startRemote :: FilePath -> Maybe Int -> Key -> Remote.Remote Annex -> CommandStart
startRemote file numcopies key remote = do startRemote file numcopies key remote = do
@ -55,12 +51,9 @@ performLocal key numcopies = lockContent key $ do
(remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key (remotes, trusteduuids) <- Remote.keyPossibilitiesTrusted key
untrusteduuids <- trustGet UnTrusted untrusteduuids <- trustGet UnTrusted
let tocheck = Remote.remotesWithoutUUID remotes (trusteduuids++untrusteduuids) let tocheck = Remote.remotesWithoutUUID remotes (trusteduuids++untrusteduuids)
success <- canDropKey key numcopies trusteduuids tocheck [] stopUnless (canDropKey key numcopies trusteduuids tocheck []) $ do
if success whenM (inAnnex key) $ removeAnnex key
then do next $ cleanupLocal key
whenM (inAnnex key) $ removeAnnex key
next $ cleanupLocal key
else stop
performRemote :: Key -> Maybe Int -> Remote.Remote Annex -> CommandPerform performRemote :: Key -> Maybe Int -> Remote.Remote Annex -> CommandPerform
performRemote key numcopies remote = lockContent key $ do performRemote key numcopies remote = lockContent key $ do
@ -75,12 +68,9 @@ performRemote key numcopies remote = lockContent key $ do
untrusteduuids <- trustGet UnTrusted untrusteduuids <- trustGet UnTrusted
let tocheck = filter (/= remote) $ let tocheck = filter (/= remote) $
Remote.remotesWithoutUUID remotes (have++untrusteduuids) Remote.remotesWithoutUUID remotes (have++untrusteduuids)
success <- canDropKey key numcopies have tocheck [uuid] stopUnless (canDropKey key numcopies have tocheck [uuid]) $ do
if success ok <- Remote.removeKey remote key
then do next $ cleanupRemote key remote ok
ok <- Remote.removeKey remote key
next $ cleanupRemote key remote ok
else stop
where where
uuid = Remote.uuid remote uuid = Remote.uuid remote

View file

@ -21,18 +21,11 @@ seek :: [CommandSeek]
seek = [withKeys start] seek = [withKeys start]
start :: Key -> CommandStart start :: Key -> CommandStart
start key = do start key = stopUnless (not <$> inAnnex key) $ do
present <- inAnnex key unlessM (Annex.getState Annex.force) $
if not present error "dropkey can cause data loss; use --force if you're sure you want to do this"
then stop showStart "dropkey" (show key)
else do next $ perform key
checkforced
showStart "dropkey" (show key)
next $ perform key
where
checkforced =
unlessM (Annex.getState Annex.force) $
error "dropkey can cause data loss; use --force if you're sure you want to do this"
perform :: Key -> CommandPerform perform :: Key -> CommandPerform
perform key = lockContent key $ do perform key = lockContent key $ do

View file

@ -23,12 +23,9 @@ seek = [withFilesInGit $ whenAnnexed start]
start :: FilePath -> (Key, Backend Annex) -> CommandStart start :: FilePath -> (Key, Backend Annex) -> CommandStart
start file (key, _) = do start file (key, _) = do
link <- calcGitLink file key link <- calcGitLink file key
l <- liftIO $ readSymbolicLink file stopUnless ((/=) link <$> liftIO (readSymbolicLink file)) $ do
if link == l showStart "fix" file
then stop next $ perform file link
else do
showStart "fix" file
next $ perform file link
perform :: FilePath -> FilePath -> CommandPerform perform :: FilePath -> FilePath -> CommandPerform
perform file link = do perform file link = do

View file

@ -22,32 +22,24 @@ seek :: [CommandSeek]
seek = [withNumCopies $ \n -> whenAnnexed $ start n] seek = [withNumCopies $ \n -> whenAnnexed $ start n]
start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart start :: Maybe Int -> FilePath -> (Key, Backend Annex) -> CommandStart
start numcopies file (key, _) = do start numcopies file (key, _) = stopUnless (not <$> inAnnex key) $
inannex <- inAnnex key autoCopies key (<) numcopies $ do
if inannex from <- Annex.getState Annex.fromremote
then stop case from of
else autoCopies key (<) numcopies $ do Nothing -> go $ perform key
from <- Annex.getState Annex.fromremote Just name -> do
case from of -- get --from = copy --from
Nothing -> go $ perform key src <- Remote.byName name
Just name -> do stopUnless (Command.Move.fromOk src key) $
-- get --from = copy --from go $ Command.Move.fromPerform src False key
src <- Remote.byName name
ok <- Command.Move.fromOk src key
if ok
then go $ Command.Move.fromPerform src False key
else stop
where where
go a = do go a = do
showStart "get" file showStart "get" file
next a next a
perform :: Key -> CommandPerform perform :: Key -> CommandPerform
perform key = do perform key = stopUnless (getViaTmp key $ getKeyFile key) $ do
ok <- getViaTmp key (getKeyFile key) next $ return True -- no cleanup needed
if ok
then next $ return True -- no cleanup needed
else stop
{- Try to find a copy of the file in one of the remotes, {- Try to find a copy of the file in one of the remotes,
- and copy it to here. -} - and copy it to here. -}

View file

@ -58,22 +58,18 @@ perform file oldkey newbackend = do
cleantmp tmpfile cleantmp tmpfile
case k of case k of
Nothing -> stop Nothing -> stop
Just (newkey, _) -> do Just (newkey, _) -> stopUnless (link src newkey) $ do
ok <- link src newkey -- Update symlink to use the new key.
if ok liftIO $ removeFile file
then do
-- Update symlink to use the new key.
liftIO $ removeFile file
-- If the old key had some -- If the old key had some
-- associated urls, record them for -- associated urls, record them for
-- the new key as well. -- the new key as well.
urls <- getUrls oldkey urls <- getUrls oldkey
unless (null urls) $ unless (null urls) $
mapM_ (setUrlPresent newkey) urls mapM_ (setUrlPresent newkey) urls
next $ Command.Add.cleanup file newkey True next $ Command.Add.cleanup file newkey True
else stop
where where
cleantmp t = liftIO $ whenM (doesFileExist t) $ removeFile t cleantmp t = liftIO $ whenM (doesFileExist t) $ removeFile t
link src newkey = getViaTmpUnchecked newkey $ \t -> do link src newkey = getViaTmpUnchecked newkey $ \t -> do

View file

@ -108,17 +108,11 @@ toPerform dest move key = moveLock move key $ do
fromStart :: Remote.Remote Annex -> Bool -> FilePath -> Key -> CommandStart fromStart :: Remote.Remote Annex -> Bool -> FilePath -> Key -> CommandStart
fromStart src move file key fromStart src move file key
| move = go | move = go
| otherwise = do | otherwise = stopUnless (inAnnex key) go
ishere <- inAnnex key
if ishere then stop else go
where where
go = do go = stopUnless (fromOk src key) $ do
ok <- fromOk src key showMoveAction move file
if ok next $ fromPerform src move key
then do
showMoveAction move file
next $ fromPerform src move key
else stop
fromOk :: Remote.Remote Annex -> Key -> Annex Bool fromOk :: Remote.Remote Annex -> Key -> Annex Bool
fromOk src key = do fromOk src key = do
u <- getUUID u <- getUUID

View file

@ -25,21 +25,17 @@ seek = [withFilesInGit $ whenAnnexed start]
{- The unannex subcommand undoes an add. -} {- The unannex subcommand undoes an add. -}
start :: FilePath -> (Key, Backend Annex) -> CommandStart start :: FilePath -> (Key, Backend Annex) -> CommandStart
start file (key, _) = do start file (key, _) = stopUnless (inAnnex key) $ do
ishere <- inAnnex key force <- Annex.getState Annex.force
if ishere unless force $ do
then do top <- fromRepo Git.workTree
force <- Annex.getState Annex.force staged <- inRepo $ LsFiles.staged [top]
unless force $ do unless (null staged) $
top <- fromRepo Git.workTree error "This command cannot be run when there are already files staged for commit."
staged <- inRepo $ LsFiles.staged [top] Annex.changeState $ \s -> s { Annex.force = True }
unless (null staged) $
error "This command cannot be run when there are already files staged for commit."
Annex.changeState $ \s -> s { Annex.force = True }
showStart "unannex" file showStart "unannex" file
next $ perform file key next $ perform file key
else stop
perform :: FilePath -> Key -> CommandPerform perform :: FilePath -> Key -> CommandPerform
perform file key = next $ cleanup file key perform file key = next $ cleanup file key