Safe Haskell | None |
---|---|
Language | Haskell2010 |
GitHub.Data.Options
Description
Module with modifiers for pull requests' and issues' listings.
Synopsis
- stateOpen :: HasState mod => mod
- stateClosed :: HasState mod => mod
- stateAll :: HasState mod => mod
- sortAscending :: HasDirection mod => mod
- sortDescending :: HasDirection mod => mod
- sortByCreated :: HasCreatedUpdated mod => mod
- sortByUpdated :: HasCreatedUpdated mod => mod
- data PullRequestMod
- prModToQueryString :: PullRequestMod -> QueryString
- optionsBase :: Text -> PullRequestMod
- optionsNoBase :: PullRequestMod
- optionsHead :: Text -> PullRequestMod
- optionsNoHead :: PullRequestMod
- sortByPopularity :: PullRequestMod
- sortByLongRunning :: PullRequestMod
- data IssueMod
- issueModToQueryString :: IssueMod -> QueryString
- sortByComments :: HasComments mod => mod
- optionsLabels :: (HasLabels mod, Foldable f) => f (Name IssueLabel) -> mod
- optionsSince :: HasSince mod => UTCTime -> mod
- optionsSinceAll :: HasSince mod => mod
- optionsAssignedIssues :: IssueMod
- optionsCreatedIssues :: IssueMod
- optionsMentionedIssues :: IssueMod
- optionsSubscribedIssues :: IssueMod
- optionsAllIssues :: IssueMod
- data IssueRepoMod
- issueRepoModToQueryString :: IssueRepoMod -> QueryString
- optionsCreator :: Name User -> IssueRepoMod
- optionsMentioned :: Name User -> IssueRepoMod
- optionsIrrelevantMilestone :: IssueRepoMod
- optionsAnyMilestone :: IssueRepoMod
- optionsNoMilestone :: IssueRepoMod
- optionsMilestone :: Id Milestone -> IssueRepoMod
- optionsIrrelevantAssignee :: IssueRepoMod
- optionsAnyAssignee :: IssueRepoMod
- optionsNoAssignee :: IssueRepoMod
- optionsAssignee :: Name User -> IssueRepoMod
- data ArtifactMod
- artifactModToQueryString :: ArtifactMod -> QueryString
- optionsArtifactName :: Text -> ArtifactMod
- data CacheMod
- cacheModToQueryString :: CacheMod -> QueryString
- optionsRef :: Text -> CacheMod
- optionsNoRef :: CacheMod
- optionsKey :: Text -> CacheMod
- optionsNoKey :: CacheMod
- optionsDirectionAsc :: CacheMod
- optionsDirectionDesc :: CacheMod
- sortByCreatedAt :: CacheMod
- sortByLastAccessedAt :: CacheMod
- sortBySizeInBytes :: CacheMod
- data WorkflowRunMod
- workflowRunModToQueryString :: WorkflowRunMod -> QueryString
- optionsWorkflowRunActor :: Text -> WorkflowRunMod
- optionsWorkflowRunBranch :: Text -> WorkflowRunMod
- optionsWorkflowRunEvent :: Text -> WorkflowRunMod
- optionsWorkflowRunStatus :: Text -> WorkflowRunMod
- optionsWorkflowRunCreated :: Text -> WorkflowRunMod
- optionsWorkflowRunHeadSha :: Text -> WorkflowRunMod
- data IssueState
- data IssueStateReason
- data MergeableState
- class HasState mod
- class HasDirection mod
- class HasCreatedUpdated mod
- class HasComments mod
- class HasLabels mod
- class HasSince mod
Common modifiers
stateClosed :: HasState mod => mod Source #
sortAscending :: HasDirection mod => mod Source #
sortDescending :: HasDirection mod => mod Source #
sortByCreated :: HasCreatedUpdated mod => mod Source #
sortByUpdated :: HasCreatedUpdated mod => mod Source #
Pull Requests
data PullRequestMod Source #
Instances
Monoid PullRequestMod Source # | |
Defined in GitHub.Data.Options Methods mappend :: PullRequestMod -> PullRequestMod -> PullRequestMod # mconcat :: [PullRequestMod] -> PullRequestMod # | |
Semigroup PullRequestMod Source # | |
Defined in GitHub.Data.Options Methods (<>) :: PullRequestMod -> PullRequestMod -> PullRequestMod # sconcat :: NonEmpty PullRequestMod -> PullRequestMod # stimes :: Integral b => b -> PullRequestMod -> PullRequestMod # | |
HasCreatedUpdated PullRequestMod Source # | |
Defined in GitHub.Data.Options | |
HasDirection PullRequestMod Source # | |
Defined in GitHub.Data.Options Methods sortDir :: SortDirection -> PullRequestMod | |
HasState PullRequestMod Source # | |
Defined in GitHub.Data.Options Methods state :: Maybe IssueState -> PullRequestMod |
optionsBase :: Text -> PullRequestMod Source #
optionsHead :: Text -> PullRequestMod Source #
Issues
Instances
Monoid IssueMod Source # | |
Semigroup IssueMod Source # | |
HasComments IssueMod Source # | |
Defined in GitHub.Data.Options Methods | |
HasCreatedUpdated IssueMod Source # | |
Defined in GitHub.Data.Options | |
HasDirection IssueMod Source # | |
Defined in GitHub.Data.Options | |
HasLabels IssueMod Source # | |
Defined in GitHub.Data.Options Methods optionsLabels :: Foldable f => f (Name IssueLabel) -> IssueMod Source # | |
HasSince IssueMod Source # | |
Defined in GitHub.Data.Options | |
HasState IssueMod Source # | |
Defined in GitHub.Data.Options Methods state :: Maybe IssueState -> IssueMod |
sortByComments :: HasComments mod => mod Source #
optionsLabels :: (HasLabels mod, Foldable f) => f (Name IssueLabel) -> mod Source #
optionsSince :: HasSince mod => UTCTime -> mod Source #
optionsSinceAll :: HasSince mod => mod Source #
Repo issues
data IssueRepoMod Source #
Instances
optionsCreator :: Name User -> IssueRepoMod Source #
Issues created by a certain user.
optionsMentioned :: Name User -> IssueRepoMod Source #
Issue mentioning the given user.
optionsIrrelevantMilestone :: IssueRepoMod Source #
Don't care about milestones (default).
optionsAnyMilestone
means there should be some milestone, but it can be any.
See https://developer.github.com/v3/issues/#list-issues-for-a-repository
optionsAnyMilestone :: IssueRepoMod Source #
Issues that have a milestone.
optionsNoMilestone :: IssueRepoMod Source #
Issues that have no milestone.
optionsMilestone :: Id Milestone -> IssueRepoMod Source #
Issues with the given milestone.
optionsIrrelevantAssignee :: IssueRepoMod Source #
Issues with or without assignee (default).
optionsAnyAssignee :: IssueRepoMod Source #
Issues assigned to someone.
optionsNoAssignee :: IssueRepoMod Source #
Issues assigned to nobody.
optionsAssignee :: Name User -> IssueRepoMod Source #
Issues assigned to a specific user.
Actions artifacts
data ArtifactMod Source #
Instances
Monoid ArtifactMod Source # | |
Defined in GitHub.Data.Options Methods mempty :: ArtifactMod # mappend :: ArtifactMod -> ArtifactMod -> ArtifactMod # mconcat :: [ArtifactMod] -> ArtifactMod # | |
Semigroup ArtifactMod Source # | |
Defined in GitHub.Data.Options Methods (<>) :: ArtifactMod -> ArtifactMod -> ArtifactMod # sconcat :: NonEmpty ArtifactMod -> ArtifactMod # stimes :: Integral b => b -> ArtifactMod -> ArtifactMod # |
optionsArtifactName :: Text -> ArtifactMod Source #
Filters artifacts by exact match on their name field.
Actions cache
optionsRef :: Text -> CacheMod Source #
optionsKey :: Text -> CacheMod Source #
Actions workflow runs
data WorkflowRunMod Source #
Instances
Monoid WorkflowRunMod Source # | |
Defined in GitHub.Data.Options Methods mappend :: WorkflowRunMod -> WorkflowRunMod -> WorkflowRunMod # mconcat :: [WorkflowRunMod] -> WorkflowRunMod # | |
Semigroup WorkflowRunMod Source # | |
Defined in GitHub.Data.Options Methods (<>) :: WorkflowRunMod -> WorkflowRunMod -> WorkflowRunMod # sconcat :: NonEmpty WorkflowRunMod -> WorkflowRunMod # stimes :: Integral b => b -> WorkflowRunMod -> WorkflowRunMod # |
Data
data IssueState Source #
Issue
or PullRequest
state
Constructors
StateOpen | |
StateClosed |
Instances
data IssueStateReason Source #
Issue
state reason
Instances
FromJSON IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods parseJSON :: Value -> Parser IssueStateReason # parseJSONList :: Value -> Parser [IssueStateReason] # | |||||
ToJSON IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods toJSON :: IssueStateReason -> Value # toEncoding :: IssueStateReason -> Encoding # toJSONList :: [IssueStateReason] -> Value # toEncodingList :: [IssueStateReason] -> Encoding # omitField :: IssueStateReason -> Bool # | |||||
Data IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IssueStateReason -> c IssueStateReason # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IssueStateReason # toConstr :: IssueStateReason -> Constr # dataTypeOf :: IssueStateReason -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IssueStateReason) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IssueStateReason) # gmapT :: (forall b. Data b => b -> b) -> IssueStateReason -> IssueStateReason # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IssueStateReason -> r # gmapQ :: (forall d. Data d => d -> u) -> IssueStateReason -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IssueStateReason -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IssueStateReason -> m IssueStateReason # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IssueStateReason -> m IssueStateReason # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IssueStateReason -> m IssueStateReason # | |||||
Bounded IssueStateReason Source # | |||||
Defined in GitHub.Data.Options | |||||
Enum IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods succ :: IssueStateReason -> IssueStateReason # pred :: IssueStateReason -> IssueStateReason # toEnum :: Int -> IssueStateReason # fromEnum :: IssueStateReason -> Int # enumFrom :: IssueStateReason -> [IssueStateReason] # enumFromThen :: IssueStateReason -> IssueStateReason -> [IssueStateReason] # enumFromTo :: IssueStateReason -> IssueStateReason -> [IssueStateReason] # enumFromThenTo :: IssueStateReason -> IssueStateReason -> IssueStateReason -> [IssueStateReason] # | |||||
Generic IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Associated Types
Methods from :: IssueStateReason -> Rep IssueStateReason x # to :: Rep IssueStateReason x -> IssueStateReason # | |||||
Show IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods showsPrec :: Int -> IssueStateReason -> ShowS # show :: IssueStateReason -> String # showList :: [IssueStateReason] -> ShowS # | |||||
Binary IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods put :: IssueStateReason -> Put # get :: Get IssueStateReason # putList :: [IssueStateReason] -> Put # | |||||
NFData IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods rnf :: IssueStateReason -> () # | |||||
Eq IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods (==) :: IssueStateReason -> IssueStateReason -> Bool # (/=) :: IssueStateReason -> IssueStateReason -> Bool # | |||||
Ord IssueStateReason Source # | |||||
Defined in GitHub.Data.Options Methods compare :: IssueStateReason -> IssueStateReason -> Ordering # (<) :: IssueStateReason -> IssueStateReason -> Bool # (<=) :: IssueStateReason -> IssueStateReason -> Bool # (>) :: IssueStateReason -> IssueStateReason -> Bool # (>=) :: IssueStateReason -> IssueStateReason -> Bool # max :: IssueStateReason -> IssueStateReason -> IssueStateReason # min :: IssueStateReason -> IssueStateReason -> IssueStateReason # | |||||
type Rep IssueStateReason Source # | |||||
Defined in GitHub.Data.Options type Rep IssueStateReason = D1 ('MetaData "IssueStateReason" "GitHub.Data.Options" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) ((C1 ('MetaCons "StateReasonCompleted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StateReasonDuplicate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StateReasonNotPlanned" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StateReasonReopened" 'PrefixI 'False) (U1 :: Type -> Type))) |
data MergeableState Source #
PullRequest
mergeable_state
Instances
FromJSON MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods parseJSON :: Value -> Parser MergeableState # parseJSONList :: Value -> Parser [MergeableState] # | |||||
ToJSON MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods toJSON :: MergeableState -> Value # toEncoding :: MergeableState -> Encoding # toJSONList :: [MergeableState] -> Value # toEncodingList :: [MergeableState] -> Encoding # omitField :: MergeableState -> Bool # | |||||
Data MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MergeableState -> c MergeableState # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MergeableState # toConstr :: MergeableState -> Constr # dataTypeOf :: MergeableState -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MergeableState) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MergeableState) # gmapT :: (forall b. Data b => b -> b) -> MergeableState -> MergeableState # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MergeableState -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MergeableState -> r # gmapQ :: (forall d. Data d => d -> u) -> MergeableState -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MergeableState -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MergeableState -> m MergeableState # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeableState -> m MergeableState # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MergeableState -> m MergeableState # | |||||
Bounded MergeableState Source # | |||||
Defined in GitHub.Data.Options | |||||
Enum MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods succ :: MergeableState -> MergeableState # pred :: MergeableState -> MergeableState # toEnum :: Int -> MergeableState # fromEnum :: MergeableState -> Int # enumFrom :: MergeableState -> [MergeableState] # enumFromThen :: MergeableState -> MergeableState -> [MergeableState] # enumFromTo :: MergeableState -> MergeableState -> [MergeableState] # enumFromThenTo :: MergeableState -> MergeableState -> MergeableState -> [MergeableState] # | |||||
Generic MergeableState Source # | |||||
Defined in GitHub.Data.Options Associated Types
Methods from :: MergeableState -> Rep MergeableState x # to :: Rep MergeableState x -> MergeableState # | |||||
Show MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods showsPrec :: Int -> MergeableState -> ShowS # show :: MergeableState -> String # showList :: [MergeableState] -> ShowS # | |||||
Binary MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods put :: MergeableState -> Put # get :: Get MergeableState # putList :: [MergeableState] -> Put # | |||||
NFData MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods rnf :: MergeableState -> () # | |||||
Eq MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods (==) :: MergeableState -> MergeableState -> Bool # (/=) :: MergeableState -> MergeableState -> Bool # | |||||
Ord MergeableState Source # | |||||
Defined in GitHub.Data.Options Methods compare :: MergeableState -> MergeableState -> Ordering # (<) :: MergeableState -> MergeableState -> Bool # (<=) :: MergeableState -> MergeableState -> Bool # (>) :: MergeableState -> MergeableState -> Bool # (>=) :: MergeableState -> MergeableState -> Bool # max :: MergeableState -> MergeableState -> MergeableState # min :: MergeableState -> MergeableState -> MergeableState # | |||||
type Rep MergeableState Source # | |||||
Defined in GitHub.Data.Options type Rep MergeableState = D1 ('MetaData "MergeableState" "GitHub.Data.Options" "github-0.30-7PDLbEAlB9u1WnWZZQOkWM" 'False) ((C1 ('MetaCons "StateUnknown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StateClean" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StateDirty" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "StateUnstable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StateBlocked" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StateBehind" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StateDraft" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Internal
Minimal complete definition
state
Instances
HasState IssueMod Source # | |
Defined in GitHub.Data.Options Methods state :: Maybe IssueState -> IssueMod | |
HasState IssueRepoMod Source # | |
Defined in GitHub.Data.Options Methods state :: Maybe IssueState -> IssueRepoMod | |
HasState PullRequestMod Source # | |
Defined in GitHub.Data.Options Methods state :: Maybe IssueState -> PullRequestMod |
class HasDirection mod Source #
Minimal complete definition
sortDir
Instances
HasDirection IssueMod Source # | |
Defined in GitHub.Data.Options | |
HasDirection IssueRepoMod Source # | |
Defined in GitHub.Data.Options Methods sortDir :: SortDirection -> IssueRepoMod | |
HasDirection PullRequestMod Source # | |
Defined in GitHub.Data.Options Methods sortDir :: SortDirection -> PullRequestMod |
class HasCreatedUpdated mod Source #
Minimal complete definition
Instances
HasCreatedUpdated IssueMod Source # | |
Defined in GitHub.Data.Options | |
HasCreatedUpdated IssueRepoMod Source # | |
Defined in GitHub.Data.Options | |
HasCreatedUpdated PullRequestMod Source # | |
Defined in GitHub.Data.Options |
class HasComments mod Source #
Minimal complete definition
Instances
HasComments IssueMod Source # | |
Defined in GitHub.Data.Options Methods | |
HasComments IssueRepoMod Source # | |
Defined in GitHub.Data.Options Methods |
Minimal complete definition
Instances
HasLabels IssueMod Source # | |
Defined in GitHub.Data.Options Methods optionsLabels :: Foldable f => f (Name IssueLabel) -> IssueMod Source # | |
HasLabels IssueRepoMod Source # | |
Defined in GitHub.Data.Options Methods optionsLabels :: Foldable f => f (Name IssueLabel) -> IssueRepoMod Source # |
Minimal complete definition
Instances
HasSince IssueMod Source # | |
Defined in GitHub.Data.Options | |
HasSince IssueRepoMod Source # | |
Defined in GitHub.Data.Options |