Skip to content

Commit

Permalink
[#136] Add --hard or --force option to the hit sync command (#174)
Browse files Browse the repository at this point in the history
Resolves #136
  • Loading branch information
chshersh authored Jun 25, 2020
1 parent 6ba3edc commit 089f115
Show file tree
Hide file tree
Showing 9 changed files with 49 additions and 44 deletions.
41 changes: 20 additions & 21 deletions src/Hit/Cli.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Options.Applicative (CommandFields, Mod, Parser, ParserInfo, argument, au
execParser, flag, flag', fullDesc, help, helper, info, infoOption, long,
metavar, option, progDesc, short, strArgument, subparser, switch)

import Hit.Core (CommitOptions (..), IssueOptions (..), Milestone (..), PushBool (..),
import Hit.Core (CommitOptions (..), ForceFlag (..), IssueOptions (..), Milestone (..),
defaultIssueOptions)
import Hit.Git (runAmend, runClear, runClone, runCommit, runCurrent, runDiff, runFix, runFresh,
runHop, runLog, runNew, runPush, runResolve, runStash, runStatus, runSync,
Expand All @@ -40,9 +40,9 @@ hit = execParser cliParser >>= \case
Fix message pushBool -> runFix message pushBool
Amend localAmend -> runAmend localAmend
Resolve branchName -> runResolve branchName
Push isForce -> runPush isForce
Sync -> runSync
Clear isForce -> runClear isForce
Push forceFlag -> runPush forceFlag
Sync forceFlag -> runSync forceFlag
Clear forceFlag -> runClear forceFlag
Current -> runCurrent >>= flip whenJust (\i -> runIssue defaultIssueOptions {ioIssueNumber = Just i})
Status commit -> runCurrent >> runStatus commit
Diff commit -> runDiff commit
Expand Down Expand Up @@ -73,13 +73,13 @@ data HitCommand
| Uncommit
| Fix
(Maybe Text) -- ^ Text of the fix commit
PushBool -- ^ Force push
ForceFlag -- ^ Force push
| Amend
Bool -- ^ Local amend
| Resolve (Maybe Text)
| Push PushBool
| Sync
| Clear PushBool
| Push ForceFlag
| Sync ForceFlag
| Clear ForceFlag
| Current
| Status (Maybe Text)
| Diff (Maybe Text)
Expand Down Expand Up @@ -154,7 +154,7 @@ commitP = do
$ long "push"
<> short 'p'
<> help "Push current branch with this commit"
coIsForcePush <- pushBoolP
coIsForcePush <- forceFlagP
pure $ Commit CommitOptions{..}

uncommitP :: Parser HitCommand
Expand All @@ -164,8 +164,8 @@ uncommitP = pure Uncommit
fixP :: Parser HitCommand
fixP = do
commitMsg <- commitMessageP
isForce <- pushBoolP
pure $ Fix commitMsg isForce
forceFlag <- forceFlagP
pure $ Fix commitMsg forceFlag

amendP :: Parser HitCommand
amendP = do
Expand All @@ -176,13 +176,13 @@ amendP = do
pure $ Amend localAmend

pushP :: Parser HitCommand
pushP = Push <$> pushBoolP
pushP = Push <$> forceFlagP

syncP :: Parser HitCommand
syncP = pure Sync
syncP = Sync <$> forceFlagP

clearP :: Parser HitCommand
clearP = Clear <$> pushBoolP
clearP = Clear <$> forceFlagP

currentP :: Parser HitCommand
currentP = pure Current
Expand Down Expand Up @@ -217,13 +217,12 @@ maybeCommitP = optional $ strArgument $ metavar "COMMIT_HASH"
commitMessageP :: Parser (Maybe Text)
commitMessageP = optional $ strArgument $ metavar "COMMIT_MESSAGE"

-- | Parse flag of force push.
pushBoolP :: Parser PushBool
pushBoolP = flag Simple Force
( long "force"
<> short 'f'
<> help "Force push"
)
-- | Parse flag of force push or sync.
forceFlagP :: Parser ForceFlag
forceFlagP = flag Simple Force
$ long "force"
<> short 'f'
<> help "Execute forcefully"

-- | Parse issue number as an argument.
issueNumP :: Parser Int
Expand Down
10 changes: 6 additions & 4 deletions src/Hit/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,16 +2,18 @@
-}

module Hit.Core
( PushBool (..)
( ForceFlag (..)
, CommitOptions (..)
, IssueOptions (..)
, Milestone (..)
, defaultIssueOptions
) where


-- | Data type to represent the type of @push@: force-push or not.
data PushBool
{- | Data type to represent the type of @push@ or @sync@: force-push
(force-reset) or not.
-}
data ForceFlag
= Simple
| Force
deriving stock (Show, Eq)
Expand All @@ -27,7 +29,7 @@ data CommitOptions = CommitOptions
-- | Push immediately.
, coPush :: !Bool
-- | Use Force push?
, coIsForcePush :: !PushBool
, coIsForcePush :: !ForceFlag
}

-- | Options of the @hit issue@ command.
Expand Down
2 changes: 1 addition & 1 deletion src/Hit/Git/Amend.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Hit.Git.Amend

import Shellmet ()

import Hit.Core (PushBool (..))
import Hit.Core (ForceFlag (..))
import Hit.Git.Push (runPush)


Expand Down
4 changes: 2 additions & 2 deletions src/Hit/Git/Clear.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,12 +7,12 @@ module Hit.Git.Clear
import Colourista (infoMessage)
import Shellmet ()

import Hit.Core (PushBool (..))
import Hit.Core (ForceFlag (..))
import Hit.Prompt (Answer (..), prompt, yesOrNoText)


-- | Remove all local changes permanently.
runClear :: PushBool -> IO ()
runClear :: ForceFlag -> IO ()
runClear = \case
Force -> clearChanges
Simple -> do
Expand Down
2 changes: 1 addition & 1 deletion src/Hit/Git/Commit.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Hit.Git.Commit
import Colourista (errorMessage)
import Shellmet ()

import Hit.Core (CommitOptions (..), PushBool (..))
import Hit.Core (CommitOptions (..), ForceFlag (..))
import Hit.Formatting (stripRfc)
import Hit.Git.Common (getCurrentBranch, issueFromBranch)
import Hit.Git.Push (runPush)
Expand Down
10 changes: 5 additions & 5 deletions src/Hit/Git/Fix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,18 +4,18 @@ module Hit.Git.Fix
( runFix
) where

import Shellmet()
import Shellmet ()

import Hit.Core (PushBool (..))
import Hit.Core (ForceFlag (..))
import Hit.Git.Push (runPush)


-- | @hit fix@ command
runFix :: Maybe Text -> PushBool -> IO ()
runFix msg pushBool = do
runFix :: Maybe Text -> ForceFlag -> IO ()
runFix msg forceFlag = do
"git" ["add", "."]
"git" ["commit", "-m", message]
runPush pushBool
runPush forceFlag
where
message :: Text
message = fromMaybe "Fix" msg
10 changes: 5 additions & 5 deletions src/Hit/Git/Push.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,14 +4,14 @@ module Hit.Git.Push
( runPush
) where

import Shellmet()
import Shellmet ()

import Hit.Core (PushBool (..))
import Hit.Core (ForceFlag (..))
import Hit.Git.Common (getCurrentBranch)


-- | @hit push@ command.
runPush :: PushBool -> IO ()
runPush isForce = getCurrentBranch >>= \branch ->
runPush :: ForceFlag -> IO ()
runPush forceFlag = getCurrentBranch >>= \branch ->
"git" $ ["push", "--set-upstream", "origin", branch]
++ ["--force" | isForce == Force]
++ ["--force" | forceFlag == Force]
12 changes: 8 additions & 4 deletions src/Hit/Git/Sync.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,16 @@ module Hit.Git.Sync
( runSync
) where

import Shellmet()
import Shellmet ()

import Hit.Core (ForceFlag (..))
import Hit.Git.Common (getCurrentBranch)


-- | @hit sync@ command.
runSync :: IO ()
runSync = getCurrentBranch >>= \branch ->
"git" ["pull", "--rebase", "origin", branch]
runSync :: ForceFlag -> IO ()
runSync forceFlag = getCurrentBranch >>= \branch -> case forceFlag of
Simple -> "git" ["pull", "--rebase", "origin", branch]
Force -> do
"git" ["fetch", "origin", branch]
"git" ["reset", "--hard", "origin/" <> branch]
2 changes: 1 addition & 1 deletion src/Hit/Git/Wip.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module Hit.Git.Wip
( runWip
) where

import Hit.Core (CommitOptions (..), PushBool (..))
import Hit.Core (CommitOptions (..), ForceFlag (..))
import Hit.Git.Commit (runCommit)
import Hit.Git.Common (getCurrentBranch)
import Hit.Git.New (runNew)
Expand Down

0 comments on commit 089f115

Please sign in to comment.