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
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
- Copyright 2011 Joachim Breitner <mail@joachim-breitner.de>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns #-}
module Command.Sync where
import Common.Annex
@ -27,9 +29,7 @@ def = [command "sync" (paramOptional (paramRepeating paramRemote))
seek :: CommandSeek
seek args = do
!branch <- currentBranch
remotes <- if null args
then defaultSyncRemotes branch
else mapM Remote.byName args
remotes <- syncRemotes branch args
showStart "syncing" $ "branch " ++ Git.Ref.describe branch ++ " with remote repositories " ++ intercalate "," (map Remote.name remotes)
showOutput
return $
@ -42,13 +42,20 @@ seek args = do
[ 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 branch = mapM Remote.byName =<< process . L.unpack <$> inRepo showref
defaultSyncRemotes branch =
mapM Remote.byName
=<< process . L.unpack <$> inRepo showref
where
syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
showref = Git.Command.pipeRead
[Param "show-ref", Param (Git.Ref.describe syncbranch)]
process = map getRemoteName . filter isRemote . map getBranchName . lines
process = map getRemoteName . filter isRemote .
map getBranchName . lines
isRemote r = "refs/remotes/" `isPrefixOf` r
getBranchName = snd . separate (== ' ')
getRemoteName = fst . separate (== '/') . snd . separate (== '/') . snd . separate (== '/')
@ -64,8 +71,8 @@ commit = do
return True
mergeLocal :: Git.Ref -> CommandStart
mergeLocal branch =
mergeFromIfExists $ Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
mergeLocal branch = mergeFromIfExists $ Git.Ref $
"refs/heads/synced/" ++ Git.Ref.describe branch
pushLocal :: Git.Ref -> CommandStart
pushLocal branch = do
@ -76,7 +83,8 @@ pushLocal branch = do
Git.Ref.describe syncBranch ++
" to the state of " ++ Git.Ref.describe branch ++ "..."
next $ next $
inRepo $ Git.Command.runBool "branch" [Param "-f", Param (Git.Ref.describe syncBranch)]
inRepo $ Git.Command.runBool "branch"
[Param "-f", Param (Git.Ref.describe syncBranch)]
else
return Nothing
@ -92,7 +100,6 @@ mergeFromIfExists fromBranch = do
showOutput
return Nothing
fetch :: Remote.Remote Annex -> CommandStart
fetch remote = do
showStart "fetching from" (Remote.name remote)
@ -102,14 +109,17 @@ fetch remote = do
inRepo $ Git.Command.runBool "fetch" [Param (Remote.name remote)]
mergeRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
mergeRemote remote branch =
mergeFromIfExists $ Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/synced/" ++ Git.Ref.describe branch
mergeRemote remote branch = mergeFromIfExists $ Git.Ref $
"refs/remotes/" ++ Remote.name remote ++
"/synced/" ++ Git.Ref.describe branch
pushRemote :: Remote.Remote Annex -> Git.Ref -> CommandStart
pushRemote remote branch = do
showStart "pushing to" (Remote.name remote)
let syncbranch = Git.Ref $ "refs/heads/synced/" ++ Git.Ref.describe branch
let syncbranchRemote = Git.Ref $ "refs/remotes/" ++ Remote.name remote ++ "/" ++ Git.Ref.describe syncbranch
let syncbranch = Git.Ref $ "refs/heads/synced/" ++
Git.Ref.describe branch
let syncbranchRemote = Git.Ref $ "refs/remotes/" ++
Remote.name remote ++ "/" ++ Git.Ref.describe syncbranch
let refspec = Git.Ref.describe branch ++ ":" ++ Git.Ref.describe syncbranch
ex <- inRepo $ Git.Ref.exists syncbranchRemote
next $ next $ do