summaryrefslogtreecommitdiff
path: root/Git/Branch.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Git/Branch.hs')
-rw-r--r--Git/Branch.hs32
1 files changed, 17 insertions, 15 deletions
diff --git a/Git/Branch.hs b/Git/Branch.hs
index 875f20f..699fbf5 100644
--- a/Git/Branch.hs
+++ b/Git/Branch.hs
@@ -2,10 +2,11 @@
-
- Copyright 2011 Joey Hess <id@joeyh.name>
-
- - Licensed under the GNU GPL version 3 or higher.
+ - Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE OverloadedStrings #-}
module Git.Branch where
@@ -15,13 +16,14 @@ import Git.Sha
import Git.Command
import qualified Git.Config
import qualified Git.Ref
-import qualified Git.BuildVersion
+
+import qualified Data.ByteString as B
{- The currently checked out branch.
-
- In a just initialized git repo before the first commit,
- symbolic-ref will show the master branch, even though that
- - branch is not created yet. So, this also looks at show-ref HEAD
+ - branch is not created yet. So, this also looks at show-ref
- to double-check.
-}
current :: Repo -> IO (Maybe Branch)
@@ -30,19 +32,19 @@ current r = do
case v of
Nothing -> return Nothing
Just branch ->
- ifM (null <$> pipeReadStrict [Param "show-ref", Param $ fromRef branch] r)
+ ifM (B.null <$> pipeReadStrict [Param "show-ref", Param $ fromRef branch] r)
( return Nothing
, return v
)
{- The current branch, which may not really exist yet. -}
currentUnsafe :: Repo -> IO (Maybe Branch)
-currentUnsafe r = parse . firstLine
+currentUnsafe r = parse . firstLine'
<$> pipeReadStrict [Param "symbolic-ref", Param "-q", Param $ fromRef Git.Ref.headRef] r
where
- parse l
- | null l = Nothing
- | otherwise = Just $ Git.Ref l
+ parse b
+ | B.null b = Nothing
+ | otherwise = Just $ Git.Ref $ decodeBS b
{- Checks if the second branch has any commits not present on the first
- branch. -}
@@ -54,7 +56,8 @@ changed origbranch newbranch repo
where
changed' :: Branch -> Branch -> [CommandParam] -> Repo -> IO String
-changed' origbranch newbranch extraps repo = pipeReadStrict ps repo
+changed' origbranch newbranch extraps repo =
+ decodeBS <$> pipeReadStrict ps repo
where
ps =
[ Param "log"
@@ -73,7 +76,7 @@ changedCommits origbranch newbranch extraps repo =
-
- This requires there to be a path from the old to the new. -}
fastForwardable :: Ref -> Ref -> Repo -> IO Bool
-fastForwardable old new repo = not . null <$>
+fastForwardable old new repo = not . B.null <$>
pipeReadStrict
[ Param "log"
, Param $ fromRef old ++ ".." ++ fromRef new
@@ -125,8 +128,7 @@ data CommitMode = ManualCommit | AutomaticCommit
{- Prevent signing automatic commits. -}
applyCommitMode :: CommitMode -> [CommandParam] -> [CommandParam]
applyCommitMode commitmode ps
- | commitmode == AutomaticCommit && not (Git.BuildVersion.older "2.0.0") =
- Param "--no-gpg-sign" : ps
+ | commitmode == AutomaticCommit = Param "--no-gpg-sign" : ps
| otherwise = ps
{- Some versions of git commit-tree honor commit.gpgsign themselves,
@@ -134,8 +136,8 @@ applyCommitMode commitmode ps
applyCommitModeForCommitTree :: CommitMode -> [CommandParam] -> Repo -> [CommandParam]
applyCommitModeForCommitTree commitmode ps r
| commitmode == ManualCommit =
- case (Git.Config.getMaybe "commit.gpgsign" r) of
- Just s | Git.Config.isTrue s == Just True ->
+ case Git.Config.getMaybe "commit.gpgsign" r of
+ Just s | Git.Config.isTrueFalse' s == Just True ->
Param "-S":ps
_ -> ps'
| otherwise = ps'
@@ -162,7 +164,7 @@ commitCommand' runner commitmode ps = runner $
commit :: CommitMode -> Bool -> String -> Branch -> [Ref] -> Repo -> IO (Maybe Sha)
commit commitmode allowempty message branch parentrefs repo = do
tree <- getSha "write-tree" $
- pipeReadStrict [Param "write-tree"] repo
+ decodeBS' <$> pipeReadStrict [Param "write-tree"] repo
ifM (cancommit tree)
( do
sha <- commitTree commitmode message parentrefs tree repo