[#156] Take care of RFCs (#162)

Resolves #156
This commit is contained in:
Veronika Romashkina 2020-06-25 09:33:27 +01:00 committed by GitHub
parent c764d6eb69
commit 5fdeaea947
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 22 additions and 38 deletions

View File

@ -1,32 +1,10 @@
module Hit.Formatting
( padLeft
, padRight
, maxLenOn
( maxLenOn
, stripRfc
) where
import qualified Data.Text as T
{- |
@padLeft n t@ pads the text 't' with spaces on the left until it reaches length 'n'.
@
padLeft 10 "hello"' " hello"
padLeft 3 "hello"' "hello"
@
-}
padLeft :: Int -> Text -> Text
padLeft n t = T.replicate (n - T.length t) " " <> t
{- |
@padRight n t@ pads the text 't' with spaces on the right until it reaches length 'n'.
@
padRight 10 "hello"' "hello "
padRight 3 "hello"' "hello"
@
-}
padRight :: Int -> Text -> Text
padRight n t = t <> T.replicate (n - T.length t) " "
{- |
@maxLenOn f xs@ finds the longest text length from 'x's by apply 'f' to each 'x'.
@ -37,3 +15,8 @@ maxLenOn show [1, 100, 1000, 2, 200] ≡ 4 -- because: Text.length (show 1000)
-}
maxLenOn :: Foldable f => (a -> Text) -> f a -> Int
maxLenOn f = foldl' (\acc a -> max acc $ T.length $ f a) 0
{- | Strip the @[RFC] @ prefix if present.
-}
stripRfc :: Text -> Text
stripRfc x = fromMaybe x $ T.stripPrefix "[RFC] " x

View File

@ -4,10 +4,11 @@ module Hit.Git.Commit
( runCommit
) where
import Shellmet ()
import Colourista (errorMessage)
import Shellmet ()
import Hit.Core (CommitOptions (..), PushBool (..))
import Hit.Formatting (stripRfc)
import Hit.Git.Common (getCurrentBranch, issueFromBranch)
import Hit.Git.Push (runPush)
import Hit.Issue (getIssueTitle, mkIssueId)
@ -43,7 +44,7 @@ runCommit CommitOptions{..} = case coName of
getCurrentIssue = issueFromBranch <$> getCurrentBranch
showMsg :: Text -> Maybe Int -> Text
showMsg msg = \case
showMsg (stripRfc -> msg) = \case
Nothing -> msg
Just n ->
let issue = "#" <> show n

View File

@ -9,6 +9,7 @@ import Data.Char (isAlphaNum, isDigit, isSpace)
import Colourista (errorMessage, infoMessage, successMessage)
import GitHub (Issue (issueNumber, issueTitle), IssueNumber (..), unIssueNumber)
import Hit.Formatting (stripRfc)
import Hit.Git.Common (getUsername)
import Hit.Issue (assignIssue, createIssue, fetchIssue, mkIssueId)
@ -91,3 +92,4 @@ assignAndDisplayBranchDescription username = \case
|| isSpace c
|| c `elem` ("_-./" :: String)
)
. stripRfc

View File

@ -7,6 +7,7 @@ module Hit.Git.Status
) where
import Colourista (blue, bold, cyan, formatWith, green, magenta, red, reset, yellow)
import Colourista.Short (b)
import Shellmet (($?), ($|))
import System.Process (callCommand)
@ -19,8 +20,8 @@ import qualified Hit.Formatting as Fmt
{- | Show stats from the given commit. If commit is not specified, uses HEAD.
-}
runStatus :: Maybe Text -> IO ()
runStatus (fromMaybe "HEAD" -> commit)
= withDeletedFiles $ withUntrackedFiles $ showPrettyDiff commit
runStatus (fromMaybe "HEAD" -> commit) =
withDeletedFiles $ withUntrackedFiles $ showPrettyDiff commit
-- | Enum that represents all possible types of file modifications.
data PatchType
@ -67,16 +68,13 @@ displayPatchType = \case
Modified -> coloredIn magenta "modified"
Renamed -> coloredIn yellow "renamed"
TypeChanged -> coloredIn cyan "type-changed"
Unmerged -> inBold "unmerged"
Unknown -> inBold "unknown"
BrokenPairing -> inBold "broken"
Unmerged -> b "unmerged"
Unknown -> b "unknown"
BrokenPairing -> b "broken"
where
coloredIn :: Text -> Text -> Text
coloredIn color = formatWith [color, bold]
inBold :: Text -> Text
inBold = formatWith [bold]
-- | Output of the @git diff --name-status@ command.
data DiffName = DiffName
{ diffNameFile :: !Text -- ^ file name
@ -213,17 +211,17 @@ showPrettyDiff commit = do
where
formatRow :: (Text, Text, Text, Text) -> Text
formatRow (fileType, fileName, fileCount, fileSigns) =
Fmt.padRight typeSize fileType
T.justifyLeft typeSize ' ' fileType
<> " "
<> Fmt.padRight nameSize fileName
<> T.justifyLeft nameSize ' ' fileName
<> " | "
<> Fmt.padLeft countSize fileCount
<> T.justifyRight countSize ' ' fileCount
<> " "
<> fileSigns
typeSize, nameSize :: Int
typeSize = Fmt.maxLenOn (\(a, _, _, _) -> a) rows
nameSize = Fmt.maxLenOn (\(_, b, _, _) -> b) rows
nameSize = Fmt.maxLenOn (\(_, x, _, _) -> x) rows
countSize = Fmt.maxLenOn (\(_, _, c, _) -> c) rows
{- | Returns 'True' if rebase is in progress. Calls magic comand and if this