Skip to content

Commit

Permalink
Merge function
Browse files Browse the repository at this point in the history
Solves #23
  • Loading branch information
andys8 committed May 15, 2021
1 parent 916403b commit 2d784f9
Show file tree
Hide file tree
Showing 7 changed files with 55 additions and 42 deletions.
6 changes: 3 additions & 3 deletions README.md
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
# git-brunch [![Travis](https://travis-ci.org/andys8/git-brunch.svg?branch=master)](https://travis-ci.org/andys8/git-brunch) ![Actions](https://github.com/andys8/git-brunch/workflows/CI/badge.svg)

A git branch checkout command-line tool
A git command-line tool to work with branches

![screenshot](https://raw.githubusercontent.com/andys8/git-brunch/master/screenshot.png)

## Features

- Checkout local or remote branch
- Rebase onto a branch
- Quickly checkout local or remote branch
- Merge or rebase a branch
- Search for a branch
- Delete a branch
- Fetch / Update
Expand Down
9 changes: 7 additions & 2 deletions app/Git.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,9 +8,9 @@ module Git
, isRemoteBranch
, listBranches
, rebaseInteractive
, merge
, toBranches
)
where
) where

import Data.Char ( isSpace )
import Data.List
Expand Down Expand Up @@ -64,6 +64,11 @@ rebaseInteractive branch = do
putStrLn $ "Rebase onto " <> fullBranchName branch
spawnGit ["rebase", "--interactive", "--autostash", fullBranchName branch]

merge :: Branch -> IO ExitCode
merge branch = do
putStrLn $ "Merge branch " <> fullBranchName branch
spawnGit ["merge", fullBranchName branch]

deleteBranch :: Branch -> IO ExitCode
deleteBranch (BranchCurrent _ ) = error "Cannot delete current branch"
deleteBranch (BranchLocal n ) = spawnGit ["branch", "-D", n]
Expand Down
58 changes: 31 additions & 27 deletions app/GitBrunch.hs
Original file line number Diff line number Diff line change
@@ -1,68 +1,68 @@
{-# LANGUAGE LambdaCase #-}
module GitBrunch
( main
)
where
) where

import Brick.Main ( halt
, continue
import Brick.Main ( continue
, halt
, suspendAndResume
)
import qualified Brick.Main as M
import Brick.Themes ( themeToAttrMap )
import Brick.Types
import qualified Brick.Widgets.Border as B
import qualified Brick.Widgets.Border.Style as BS
import qualified Brick.Widgets.Center as C
import Brick.Widgets.Core
import qualified Brick.Widgets.Dialog as D
import qualified Brick.Widgets.Edit as E
import qualified Brick.Widgets.List as L
import Control.Exception ( SomeException
, catch
)
import Control.Monad
import Data.Char
import Data.List
import Data.Maybe ( fromMaybe )
import qualified Data.Vector as Vec
import Graphics.Vty hiding ( update )
import Lens.Micro ( (^.)
, (.~)
, (%~)
import Lens.Micro ( (%~)
, (&)
, (.~)
, Lens'
, (^.)
, lens
)
import System.Exit
import qualified Brick.Main as M
import qualified Brick.Widgets.Border as B
import qualified Brick.Widgets.Border.Style as BS
import qualified Brick.Widgets.Center as C
import qualified Brick.Widgets.Dialog as D
import qualified Brick.Widgets.Edit as E
import qualified Brick.Widgets.List as L
import qualified Data.Vector as Vec

import Git ( Branch(..) )
import Theme
import qualified Git
import Theme


data Name = Local | Remote | Filter deriving (Ord, Eq, Show)
data RemoteName = RLocal | RRemote deriving (Eq)
data GitCommand = GitRebase | GitCheckout | GitDeleteBranch deriving (Ord, Eq)
data GitCommand = GitRebase | GitMerge | GitCheckout | GitDeleteBranch deriving (Ord, Eq)
data DialogResult = SetDialog Dialog | EndDialog DialogOption
data DialogOption = Cancel | Confirm
type Dialog = D.Dialog DialogOption

data State = State
{ _focus :: RemoteName
, _gitCommand :: GitCommand
, _branches :: [Branch]
, _localBranches :: L.List Name Branch
, _remoteBranches :: L.List Name Branch
, _dialog :: Maybe Dialog
, _filter :: E.Editor String Name
{ _focus :: RemoteName
, _gitCommand :: GitCommand
, _branches :: [Branch]
, _localBranches :: L.List Name Branch
, _remoteBranches :: L.List Name Branch
, _dialog :: Maybe Dialog
, _filter :: E.Editor String Name
, _isEditingFilter :: Bool
}


instance (Show GitCommand) where
instance Show GitCommand where
show GitCheckout = "checkout"
show GitRebase = "rebase"
show GitMerge = "merge"
show GitDeleteBranch = "delete"


Expand All @@ -81,6 +81,7 @@ main = do
gitFunction = \case
GitCheckout -> Git.checkout
GitRebase -> Git.rebaseInteractive
GitMerge -> Git.merge
GitDeleteBranch -> Git.deleteBranch

emptyState :: State
Expand Down Expand Up @@ -126,11 +127,11 @@ appDraw state =
, C.hCenter $ toBranchList RRemote remoteBranchesL
]
instructions = maxWidth 100 $ hBox
[ drawInstruction "HJKL" "move"
, drawInstruction "Enter" "checkout"
[ drawInstruction "Enter" "checkout"
, drawInstruction "/" "filter"
, drawInstruction "F" "fetch"
, drawInstruction "R" "rebase"
, drawInstruction "M" "merge"
, drawInstruction "D" "delete"
]

Expand Down Expand Up @@ -225,6 +226,7 @@ appHandleEventMain state (VtyEvent e) =
confirmDelete Nothing = continue state
endWithCheckout = halt $ state { _gitCommand = GitCheckout }
endWithRebase = halt $ state { _gitCommand = GitRebase }
endWithMerge = halt $ state { _gitCommand = GitMerge }
focusLocal = focusBranches RLocal state
focusRemote = focusBranches RRemote state
doFetch = suspendAndResume (fetchBranches state)
Expand All @@ -245,7 +247,9 @@ appHandleEventMain state (VtyEvent e) =
EvKey (KChar 'f') [MCtrl] -> startEditingFilter
EvKey (KChar 'd') [] -> confirmDelete (selectedBranch state)
EvKey KEnter [] -> endWithCheckout
EvKey (KChar 'c') [] -> endWithCheckout
EvKey (KChar 'r') [] -> endWithRebase
EvKey (KChar 'm') [] -> endWithMerge
EvKey KLeft [] -> focusLocal
EvKey (KChar 'h') [] -> focusLocal
EvKey KRight [] -> focusRemote
Expand Down
4 changes: 2 additions & 2 deletions app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
module Main where

import Data.Version ( showVersion )
import Options.Applicative
import Paths_git_brunch ( version )
import Data.Version ( showVersion )

import qualified GitBrunch

Expand All @@ -15,7 +15,7 @@ main = run =<< execParser opts
where
opts = info
(versionParser <|> pure RunGitBrunch <**> helper)
(header "git-brunch - A git checkout and rebase command-line tool")
(header "git-brunch - A git command-line tool to work with branches")


run :: Mode -> IO ()
Expand Down
6 changes: 3 additions & 3 deletions app/Theme.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,11 +5,11 @@ import Brick.AttrMap ( AttrName
)
import Brick.Themes
import Brick.Util
import Graphics.Vty
import qualified Brick.Widgets.Dialog as Dialog
import qualified Brick.Widgets.List as List
import Brick.Widgets.Border as Border
import qualified Brick.Widgets.Dialog as Dialog
import qualified Brick.Widgets.Edit as Edit
import qualified Brick.Widgets.List as List
import Graphics.Vty

theme :: Theme
theme = newTheme
Expand Down
12 changes: 8 additions & 4 deletions git-brunch.cabal
Original file line number Diff line number Diff line change
@@ -1,10 +1,10 @@
cabal-version: 1.12

-- This file has been generated from package.yaml by hpack version 0.33.0.
-- This file has been generated from package.yaml by hpack version 0.34.4.
--
-- see: https://github.com/sol/hpack
--
-- hash: 643cd917a331afd2c5c769ae081cd6f382eec74c30471e6b5b3ac9315c3df792
-- hash: c32cfb3e007291aaae447a467d7a182f94a45c06f63f0c1cb46886481916468d

name: git-brunch
version: 1.4.4.0
Expand Down Expand Up @@ -39,7 +39,9 @@ executable git-brunch
Paths_git_brunch
hs-source-dirs:
app
default-extensions: StrictData OverloadedStrings
default-extensions:
StrictData
OverloadedStrings
build-depends:
base >=4.7 && <5
, brick
Expand All @@ -65,7 +67,9 @@ test-suite git-brunch-test
hs-source-dirs:
test
app
default-extensions: StrictData OverloadedStrings
default-extensions:
StrictData
OverloadedStrings
ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
Expand Down
2 changes: 1 addition & 1 deletion test/Spec.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
import Test.Hspec
import Git
import Test.Hspec

main :: IO ()
main = hspec $ describe "Git.toBranch" $ do
Expand Down

0 comments on commit 2d784f9

Please sign in to comment.