Skip to content

Commit

Permalink
[#157] Show issues from the current milestone (#169)
Browse files Browse the repository at this point in the history
* [#157] Show issues from the current milestone

Resolves #157

* Update src/Hit/Issue.hs

Co-authored-by: Dmitrii Kovanikov <kovanikov@gmail.com>

* Add more useful warning messages

Co-authored-by: Dmitrii Kovanikov <kovanikov@gmail.com>
  • Loading branch information
vrom911 and chshersh authored Jun 25, 2020
1 parent fb00d5c commit d6f6559
Show file tree
Hide file tree
Showing 4 changed files with 113 additions and 24 deletions.
4 changes: 4 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,10 @@ The changelog is available [on GitHub][2].
Filter out PRs from the list of all issues in the `hit issue` command.
* [#154](https://github.com/kowainik/hit-on/issues/154):
Add `--date=now` to the `amend` command.
* [#157](https://github.com/kowainik/hit-on/issues/157):
Add milestone related options to the `hit issue` command:
* `-m|--current-milestone` — filter out issues in the current milestone.
* `--milestone=ID` — filter out issues in the given milestone.

### 0.1.0.0 — Aug 3, 2019

Expand Down
44 changes: 30 additions & 14 deletions src/Hit/Cli.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,12 +11,13 @@ import Colourista (blue, bold, formatWith)
import Data.Version (showVersion)
import Development.GitRev (gitCommitDate, gitHash)
import Options.Applicative (CommandFields, Mod, Parser, ParserInfo, argument, auto, command,
execParser, flag, fullDesc, help, helper, info, infoOption, long,
metavar, progDesc, short, strArgument, subparser, switch)
execParser, flag, flag', fullDesc, help, helper, info, infoOption, long,
metavar, option, progDesc, short, strArgument, subparser, switch)

import Hit.Core (CommitOptions (..), PushBool (..))
import Hit.Git (getUsername, runAmend, runClear, runClone, runCommit, runCurrent, runDiff, runFix,
runFresh, runHop, runLog, runNew, runPush, runResolve, runStash, runStatus, runSync,
import Hit.Core (CommitOptions (..), IssueOptions (..), Milestone (..), PushBool (..),
defaultIssueOptions)
import Hit.Git (runAmend, runClear, runClone, runCommit, runCurrent, runDiff, runFix, runFresh,
runHop, runLog, runNew, runPush, runResolve, runStash, runStatus, runSync,
runUncommit, runUnstash)
import Hit.Issue (runIssue)
import Hit.Prompt (arrow)
Expand All @@ -30,9 +31,7 @@ hit = execParser cliParser >>= \case
Hop branchName -> runHop branchName
Fresh branchName -> runFresh branchName
New createIssue issueNum -> runNew createIssue issueNum
Issue issueNum me -> if me
then getUsername >>= runIssue issueNum . Just
else runIssue issueNum Nothing
Issue issueOpts -> runIssue issueOpts
Stash -> runStash
Unstash -> runUnstash
Commit opts -> runCommit opts
Expand All @@ -43,7 +42,7 @@ hit = execParser cliParser >>= \case
Push isForce -> runPush isForce
Sync -> runSync
Clear isForce -> runClear isForce
Current -> runCurrent >>= flip whenJust (flip runIssue Nothing . Just)
Current -> runCurrent >>= flip whenJust (\i -> runIssue defaultIssueOptions {ioIssueNumber = Just i})
Status commit -> runCurrent >> runStatus commit
Diff commit -> runDiff commit
Clone name -> runClone name
Expand All @@ -65,7 +64,7 @@ data HitCommand
| New
Bool -- ^ Should create issue as well?
Text -- ^ Issue or branch name
| Issue (Maybe Int) Bool
| Issue IssueOptions
| Stash
| Unstash
| Commit CommitOptions
Expand Down Expand Up @@ -128,12 +127,12 @@ newP = do

issueP :: Parser HitCommand
issueP = do
num <- optional issueNumP
me <- switch
ioIssueNumber <- optional issueNumP
ioMe <- switch
$ long "me"
<> short 'm'
<> help "Assigned to me"
pure $ Issue num me
ioMilestone <- milestoneP
pure $ Issue IssueOptions {..}

stashP :: Parser HitCommand
stashP = pure Stash
Expand Down Expand Up @@ -224,6 +223,23 @@ pushBoolP = flag Simple Force
issueNumP :: Parser Int
issueNumP = argument auto $ metavar "ISSUE_NUMBER"

milestoneP :: Parser (Maybe Milestone)
milestoneP = optional (curMilestone <|> milestoneId)
where
curMilestone :: Parser Milestone
curMilestone = flag' CurrentMilestone $ mconcat
[ long "current-milestone"
, short 'm'
, help "Use the Project's current Milestone"
]

milestoneId :: Parser Milestone
milestoneId = MilestoneId <$> option auto
( long "milestone"
<> help "Specify the project's Milestone ID"
<> metavar "MILESTONE_ID"
)

-- | Show the version of the tool.
versionP :: Parser (a -> a)
versionP = infoOption hitVersion
Expand Down
23 changes: 23 additions & 0 deletions src/Hit/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,9 @@
module Hit.Core
( PushBool (..)
, CommitOptions (..)
, IssueOptions (..)
, Milestone (..)
, defaultIssueOptions
) where


Expand All @@ -26,3 +29,23 @@ data CommitOptions = CommitOptions
-- | Use Force push?
, coIsForcePush :: !PushBool
}

-- | Options of the @hit issue@ command.
data IssueOptions = IssueOptions
{ ioIssueNumber :: !(Maybe Int)
, ioMe :: !Bool
, ioMilestone :: !(Maybe Milestone)
}

-- | Internal representation of the GutHub Milestone in CLI.
data Milestone
= CurrentMilestone
| MilestoneId !Int
deriving stock (Show)

defaultIssueOptions :: IssueOptions
defaultIssueOptions = IssueOptions
{ ioIssueNumber = Nothing
, ioMe = False
, ioMilestone = Nothing
}
66 changes: 56 additions & 10 deletions src/Hit/Issue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,16 +16,21 @@ module Hit.Issue
, showIssueName
) where

import Colourista (blue, blueBg, bold, errorMessage, formatWith, green, red, reset, successMessage)
import Colourista (blue, blueBg, bold, errorMessage, formatWith, green, red, reset, successMessage,
warningMessage)
import Data.Vector (Vector)
import GitHub (Error (..), Id, Issue (..), IssueLabel (..), IssueState (..), Name, Owner, Repo,
SimpleUser (..), User, getUrl, mkId, mkName, unIssueNumber, untagName)
SimpleUser (..), User, getUrl, milestoneNumber, mkId, mkName, unIssueNumber, untagId,
untagName)
import GitHub.Auth (Auth (OAuth))
import GitHub.Data.Options (stateOpen)
import GitHub.Endpoints.Issues (EditIssue (..), NewIssue (..), editOfIssue, issue', issuesForRepo')
import GitHub.Endpoints.Issues.Milestones (milestones')
import Shellmet (($|))
import System.Environment (lookupEnv)

import Hit.Core (IssueOptions (..), Milestone (..))
import Hit.Git.Common (getUsername)
import Hit.Prompt (arrow)

import qualified Hit.Formatting as Fmt
Expand All @@ -39,26 +44,40 @@ import qualified GitHub.Endpoints.Issues as GitHub
----------------------------------------------------------------------------

-- | Run the @issue@ command.
runIssue :: Maybe Int -> Maybe Text -> IO ()
runIssue issue me = case issue of
runIssue :: IssueOptions -> IO ()
runIssue IssueOptions{..} = case ioIssueNumber of
Just num -> getIssue $ mkIssueId num
Nothing -> getAllIssues me
Nothing -> me >>= getAllIssues ioMilestone
where
me :: IO (Maybe Text)
me = if ioMe
then Just <$> getUsername
else pure Nothing

{- | Get the list of the opened issues for the current project and
display short information about each issue.
-}
getAllIssues :: Maybe Text -> IO ()
getAllIssues me = withOwnerRepo (\t o r -> issuesForRepo' t o r stateOpen) >>= \case
getAllIssues
:: Maybe Milestone -- ^ Project Milestone
-> Maybe Text -- ^ User name of the assignee
-> IO ()
getAllIssues milestone me = withOwnerRepo (\t o r -> issuesForRepo' t o r stateOpen) >>= \case
Left err -> errorMessage $ show err
Right is -> do
let maxLen = Fmt.maxLenOn showIssueNumber is
for_ (filterIssues is) $ \i -> do
milestoneId <- getMilestoneId
for_ (filterIssues milestoneId is) $ \i -> do
let thisLen = T.length $ showIssueNumber i
padSize = maxLen - thisLen
putTextLn $ showIssueName blue padSize i
where
filterIssues :: Vector Issue -> Vector Issue
filterIssues = V.filter (\i -> my i && isNotPR i)
filterIssues :: Maybe Int -> Vector Issue -> Vector Issue
filterIssues milestoneId = V.filter
(\i ->
isNotPR i
&& my i
&& i `isInMilestone` milestoneId
)

my :: Issue -> Bool
my issue = case me of
Expand All @@ -68,6 +87,20 @@ getAllIssues me = withOwnerRepo (\t o r -> issuesForRepo' t o r stateOpen) >>= \
isNotPR :: Issue -> Bool
isNotPR Issue{..} = isNothing issuePullRequest

getMilestoneId :: IO (Maybe Int)
getMilestoneId = case milestone of
Just (MilestoneId mId) -> pure $ Just mId
Just CurrentMilestone -> fetchCurrentMilestoneId
Nothing -> pure Nothing

isInMilestone :: Issue -> Maybe Int -> Bool
isInMilestone Issue{..} = \case
Just milestoneId -> issueMilestoneId == Just milestoneId
Nothing -> True
where
issueMilestoneId :: Maybe Int
issueMilestoneId = untagId . milestoneNumber <$> issueMilestone

-- | Show issue number with alignment and its name.
showIssueName :: Text -> Int -> Issue -> Text
showIssueName colorCode padSize i@Issue{..} =
Expand Down Expand Up @@ -185,6 +218,19 @@ fetchIssue iNum = withOwnerRepo (\t o r -> issue' t o r iNum) >>= \case
Left err -> errorMessage (show err) >> exitFailure
Right issue -> pure issue

{- | Fetches all open milestones. Then figure out the current one and return its
ID as 'Int'.
If it could not fetch, or there is no open milestones then prints a warning
message and returns 'Nothing'.
-}
fetchCurrentMilestoneId :: IO (Maybe Int)
fetchCurrentMilestoneId = withOwnerRepo milestones' >>= \case
Left err -> Nothing <$ warningMessage ("Could not fetch the milestones\n " <> show err)
Right ms -> case sortBy (flip compare) $ map (untagId . milestoneNumber) $ toList ms of
[] -> warningMessage "There are no open milestones for this project" >> pure Nothing
m:_ -> pure $ Just m

-- | Perform action by given auth token, owner and repo name.
withOwnerRepo
:: (Maybe Auth -> Name Owner -> Name Repo -> IO (Either Error a))
Expand Down

0 comments on commit d6f6559

Please sign in to comment.