update to my indentation style

This commit is contained in:
Joey Hess 2011-12-30 16:24:30 -04:00
parent 5728bb58e0
commit 5d17da5eb3

View file

@ -1,11 +1,13 @@
{-# LANGUAGE BangPatterns #-}
{- git-annex command {- git-annex command
- -
- Copyright 2011 Joey Hess <joey@kitenet.net> - Copyright 2011 Joey Hess <joey@kitenet.net>
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
{-# LANGUAGE BangPatterns #-}
module Command.Sync where module Command.Sync where
import Common.Annex import Common.Annex
@ -21,37 +23,42 @@ import qualified Data.ByteString.Lazy.Char8 as L
def :: [Command] def :: [Command]
def = [command "sync" (paramOptional (paramRepeating paramRemote)) def = [command "sync" (paramOptional (paramRepeating paramRemote))
[seek] "synchronize local repository with remote repositories"] [seek] "synchronize local repository with remote repositories"]
-- syncing involves several operations, any of which can independantly fail -- syncing involves several operations, any of which can independantly fail
seek :: CommandSeek seek :: CommandSeek
seek args = do seek args = do
!branch <- currentBranch !branch <- currentBranch
remotes <- if null args remotes <- syncRemotes branch args
then defaultSyncRemotes branch showStart "syncing" $ "branch " ++ Git.Ref.describe branch ++ " with remote repositories " ++ intercalate "," (map Remote.name remotes)
else mapM Remote.byName args showOutput
showStart "syncing" $ "branch " ++ Git.Ref.describe branch ++ " with remote repositories " ++ intercalate "," (map Remote.name remotes) return $
showOutput [ commit
return $ , mergeLocal branch
[ commit ] ++
, mergeLocal branch [ fetch remote | remote <- remotes ] ++
] ++ [ mergeRemote remote branch | remote <- remotes ] ++
[ fetch remote | remote <- remotes ] ++ [ mergeAnnex ] ++
[ mergeRemote remote branch | remote <- remotes ] ++ [ pushLocal branch ] ++
[ mergeAnnex ] ++ [ pushRemote remote branch | remote <- remotes ]
[ pushLocal branch ] ++
[ pushRemote remote branch | remote <- remotes ] syncRemotes :: Git.Ref -> [String] -> Annex [Remote.Remote Annex]
syncRemotes branch [] = defaultSyncRemotes branch
syncRemotes _ rs = mapM Remote.byName rs
defaultSyncRemotes :: Git.Ref -> Annex [Remote.Remote Annex] defaultSyncRemotes :: Git.Ref -> Annex [Remote.Remote Annex]
defaultSyncRemotes branch = mapM Remote.byName =<< process . L.unpack <$> inRepo showref defaultSyncRemotes branch =
where mapM Remote.byName
syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch =<< process . L.unpack <$> inRepo showref
showref = Git.Command.pipeRead where
[Param "show-ref", Param (Git.Ref.describe syncbranch)] syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
process = map getRemoteName . filter isRemote . map getBranchName . lines showref = Git.Command.pipeRead
isRemote r = "refs/remotes/" `isPrefixOf` r [Param "show-ref", Param (Git.Ref.describe syncbranch)]
getBranchName = snd . separate (== ' ') process = map getRemoteName . filter isRemote .
getRemoteName = fst . separate (== '/') . snd . separate (== '/') . snd . separate (== '/') map getBranchName . lines
isRemote r = "refs/remotes/" `isPrefixOf` r
getBranchName = snd . separate (== ' ')
getRemoteName = fst . separate (== '/') . snd . separate (== '/') . snd . separate (== '/')
commit :: CommandStart commit :: CommandStart
commit = do commit = do
@ -64,34 +71,34 @@ commit = do
return True return True
mergeLocal :: Git.Ref -> CommandStart mergeLocal :: Git.Ref -> CommandStart
mergeLocal branch = mergeLocal branch = mergeFromIfExists $ Git.Ref $
mergeFromIfExists $ Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch "refs/heads/synced/" ++ Git.Ref.describe branch
pushLocal :: Git.Ref -> CommandStart pushLocal :: Git.Ref -> CommandStart
pushLocal branch = do pushLocal branch = do
let syncBranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch let syncBranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
ex <- inRepo $ Git.Ref.exists syncBranch ex <- inRepo $ Git.Ref.exists syncBranch
if ex then do if ex then do
showStart "updateing" $ showStart "updateing" $
Git.Ref.describe syncBranch ++ Git.Ref.describe syncBranch ++
" to the state of " ++ Git.Ref.describe branch ++ "..." " to the state of " ++ Git.Ref.describe branch ++ "..."
next $ next $ next $ next $
inRepo $ Git.Command.runBool "branch" [Param "-f", Param (Git.Ref.describe syncBranch)] inRepo $ Git.Command.runBool "branch"
else [Param "-f", Param (Git.Ref.describe syncBranch)]
return Nothing else
return Nothing
mergeFromIfExists :: Git.Ref -> CommandStart mergeFromIfExists :: Git.Ref -> CommandStart
mergeFromIfExists fromBranch = do mergeFromIfExists fromBranch = do
ex <- inRepo $ Git.Ref.exists fromBranch ex <- inRepo $ Git.Ref.exists fromBranch
if ex then do if ex then do
showStart "merging" $ Git.Ref.describe fromBranch ++ "..." showStart "merging" $ Git.Ref.describe fromBranch ++ "..."
next $ next $ next $ next $
inRepo $ Git.Command.runBool "merge" [Param (show fromBranch)] inRepo $ Git.Command.runBool "merge" [Param (show fromBranch)]
else do else do
showNote $ Git.Ref.describe fromBranch ++ " does not exist, not merging." showNote $ Git.Ref.describe fromBranch ++ " does not exist, not merging."
showOutput showOutput
return Nothing return Nothing
fetch :: Remote.Remote Annex -> CommandStart fetch :: Remote.Remote Annex -> CommandStart
fetch remote = do fetch remote = do
@ -102,22 +109,25 @@ fetch remote = do
inRepo $ Git.Command.runBool "fetch" [Param (Remote.name remote)] inRepo $ Git.Command.runBool "fetch" [Param (Remote.name remote)]
mergeRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart mergeRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
mergeRemote remote branch = mergeRemote remote branch = mergeFromIfExists $ Git.Ref $
mergeFromIfExists $ Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/synced/" ++ Git.Ref.describe branch "refs/remotes/" ++ Remote.name remote ++
"/synced/" ++ Git.Ref.describe branch
pushRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart pushRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
pushRemote remote branch = do pushRemote remote branch = do
showStart "pushing to" (Remote.name remote) showStart "pushing to" (Remote.name remote)
let syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch let syncbranch = Git.Ref $ "refs/heads/synced/" ++
let syncbranchRemote = Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/" ++ Git.Ref.describe syncbranch Git.Ref.describe branch
let refspec = Git.Ref.describe branch ++ ":" ++ Git.Ref.describe syncbranch let syncbranchRemote = Git.Ref $ "refs/remotes/" ++
ex <- inRepo $ Git.Ref.exists syncbranchRemote Remote.name remote ++ "/" ++ Git.Ref.describe syncbranch
next $ next $ do let refspec = Git.Ref.describe branch ++ ":" ++ Git.Ref.describe syncbranch
showOutput ex <- inRepo $ Git.Ref.exists syncbranchRemote
inRepo $ Git.Command.runBool "push" $ next $ next $ do
[ Param (Remote.name remote) showOutput
, Param (Git.Ref.describe Annex.Branch.name) ] ++ inRepo $ Git.Command.runBool "push" $
[ Param refspec | ex ] [ Param (Remote.name remote)
, Param (Git.Ref.describe Annex.Branch.name) ] ++
[ Param refspec | ex ]
currentBranch :: Annex Git.Ref currentBranch :: Annex Git.Ref
currentBranch = Git.Ref . firstLine . L.unpack <$> currentBranch = Git.Ref . firstLine . L.unpack <$>