| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GitHub.Data.Issues
Synopsis
- data Issue = Issue {- issueClosedAt :: !(Maybe UTCTime)
- issueUpdatedAt :: !UTCTime
- issueEventsUrl :: !URL
- issueHtmlUrl :: !(Maybe URL)
- issueClosedBy :: !(Maybe SimpleUser)
- issueLabels :: !(Vector IssueLabel)
- issueNumber :: !IssueNumber
- issueAssignees :: !(Vector SimpleUser)
- issueUser :: !SimpleUser
- issueTitle :: !Text
- issuePullRequest :: !(Maybe PullRequestReference)
- issueUrl :: !URL
- issueCreatedAt :: !UTCTime
- issueBody :: !(Maybe Text)
- issueState :: !IssueState
- issueId :: !(Id Issue)
- issueComments :: !Int
- issueMilestone :: !(Maybe Milestone)
- issueStateReason :: !(Maybe IssueStateReason)
 
- data NewIssue = NewIssue {- newIssueTitle :: !Text
- newIssueBody :: !(Maybe Text)
- newIssueAssignees :: !(Vector (Name User))
- newIssueMilestone :: !(Maybe (Id Milestone))
- newIssueLabels :: !(Maybe (Vector (Name IssueLabel)))
 
- data EditIssue = EditIssue {- editIssueTitle :: !(Maybe Text)
- editIssueBody :: !(Maybe Text)
- editIssueAssignees :: !(Maybe (Vector (Name User)))
- editIssueState :: !(Maybe IssueState)
- editIssueMilestone :: !(Maybe (Id Milestone))
- editIssueLabels :: !(Maybe (Vector (Name IssueLabel)))
 
- data IssueComment = IssueComment {}
- data EventType- = Mentioned
- | Subscribed
- | Unsubscribed
- | Referenced
- | Merged
- | Assigned
- | Closed
- | Reopened
- | ActorUnassigned
- | Labeled
- | Unlabeled
- | Milestoned
- | Demilestoned
- | Renamed
- | Locked
- | Unlocked
- | HeadRefDeleted
- | HeadRefRestored
- | ReviewRequested
- | ReviewDismissed
- | ReviewRequestRemoved
- | MarkedAsDuplicate
- | UnmarkedAsDuplicate
- | AddedToProject
- | MovedColumnsInProject
- | RemovedFromProject
- | ConvertedNoteToIssue
 
- data IssueEvent = IssueEvent {- issueEventActor :: !SimpleUser
- issueEventType :: !EventType
- issueEventCommitId :: !(Maybe Text)
- issueEventUrl :: !URL
- issueEventCreatedAt :: !UTCTime
- issueEventId :: !Int
- issueEventIssue :: !(Maybe Issue)
- issueEventLabel :: !(Maybe IssueLabel)
 
Documentation
Constructors
| Issue | |
| Fields 
 | |
Instances
Constructors
| NewIssue | |
| Fields 
 | |
Instances
| ToJSON NewIssue Source # | |
| Defined in GitHub.Data.Issues | |
| Data NewIssue Source # | |
| Defined in GitHub.Data.Issues Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NewIssue -> c NewIssue # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NewIssue # toConstr :: NewIssue -> Constr # dataTypeOf :: NewIssue -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NewIssue) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NewIssue) # gmapT :: (forall b. Data b => b -> b) -> NewIssue -> NewIssue # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NewIssue -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NewIssue -> r # gmapQ :: (forall d. Data d => d -> u) -> NewIssue -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NewIssue -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NewIssue -> m NewIssue # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NewIssue -> m NewIssue # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NewIssue -> m NewIssue # | |
| Generic NewIssue Source # | |
| Show NewIssue Source # | |
| Binary NewIssue Source # | |
| NFData NewIssue Source # | |
| Defined in GitHub.Data.Issues | |
| Eq NewIssue Source # | |
| Ord NewIssue Source # | |
| Defined in GitHub.Data.Issues | |
| type Rep NewIssue Source # | |
| Defined in GitHub.Data.Issues type Rep NewIssue = D1 ('MetaData "NewIssue" "GitHub.Data.Issues" "github-0.29-8pCAynMhaqD8pNGAeWnyh4" 'False) (C1 ('MetaCons "NewIssue" 'PrefixI 'True) ((S1 ('MetaSel ('Just "newIssueTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "newIssueBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "newIssueAssignees") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector (Name User))) :*: (S1 ('MetaSel ('Just "newIssueMilestone") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Id Milestone))) :*: S1 ('MetaSel ('Just "newIssueLabels") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Vector (Name IssueLabel)))))))) | |
Constructors
| EditIssue | |
| Fields 
 | |
Instances
data IssueComment Source #
Constructors
| IssueComment | |
| Fields 
 | |
Instances
Constructors
| Mentioned | The actor was @mentioned in an issue body. | 
| Subscribed | The actor subscribed to receive notifications for an issue. | 
| Unsubscribed | The issue was unsubscribed from by the actor. | 
| Referenced | The issue was referenced from a commit message. The commit_id attribute is the commit SHA1 of where that happened. | 
| Merged | The issue was merged by the actor. The commit_id attribute is the SHA1 of the HEAD commit that was merged. | 
| Assigned | The issue was assigned to the actor. | 
| Closed | The issue was closed by the actor. When the commit_id is present, it identifies the commit that closed the issue using “closes / fixes #NN” syntax. | 
| Reopened | The issue was reopened by the actor. | 
| ActorUnassigned | The issue was unassigned to the actor | 
| Labeled | A label was added to the issue. | 
| Unlabeled | A label was removed from the issue. | 
| Milestoned | The issue was added to a milestone. | 
| Demilestoned | The issue was removed from a milestone. | 
| Renamed | The issue title was changed. | 
| Locked | The issue was locked by the actor. | 
| Unlocked | The issue was unlocked by the actor. | 
| HeadRefDeleted | The pull request’s branch was deleted. | 
| HeadRefRestored | The pull request’s branch was restored. | 
| ReviewRequested | The actor requested review from the subject on this pull request. | 
| ReviewDismissed | The actor dismissed a review from the pull request. | 
| ReviewRequestRemoved | The actor removed the review request for the subject on this pull request. | 
| MarkedAsDuplicate | A user with write permissions marked an issue as a duplicate of another issue or a pull request as a duplicate of another pull request. | 
| UnmarkedAsDuplicate | An issue that a user had previously marked as a duplicate of another issue is no longer considered a duplicate, or a pull request that a user had previously marked as a duplicate of another pull request is no longer considered a duplicate. | 
| AddedToProject | The issue was added to a project board. | 
| MovedColumnsInProject | The issue was moved between columns in a project board. | 
| RemovedFromProject | The issue was removed from a project board. | 
| ConvertedNoteToIssue | The issue was created by converting a note in a project board to an issue. | 
Instances
| FromJSON EventType Source # | |
| Data EventType Source # | |
| Defined in GitHub.Data.Issues Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventType -> c EventType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventType # toConstr :: EventType -> Constr # dataTypeOf :: EventType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EventType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventType) # gmapT :: (forall b. Data b => b -> b) -> EventType -> EventType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventType -> r # gmapQ :: (forall d. Data d => d -> u) -> EventType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EventType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventType -> m EventType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventType -> m EventType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventType -> m EventType # | |
| Bounded EventType Source # | |
| Enum EventType Source # | |
| Defined in GitHub.Data.Issues Methods succ :: EventType -> EventType # pred :: EventType -> EventType # fromEnum :: EventType -> Int # enumFrom :: EventType -> [EventType] # enumFromThen :: EventType -> EventType -> [EventType] # enumFromTo :: EventType -> EventType -> [EventType] # enumFromThenTo :: EventType -> EventType -> EventType -> [EventType] # | |
| Generic EventType Source # | |
| Show EventType Source # | |
| Binary EventType Source # | |
| NFData EventType Source # | |
| Defined in GitHub.Data.Issues | |
| Eq EventType Source # | |
| Ord EventType Source # | |
| type Rep EventType Source # | |
| Defined in GitHub.Data.Issues type Rep EventType = D1 ('MetaData "EventType" "GitHub.Data.Issues" "github-0.29-8pCAynMhaqD8pNGAeWnyh4" 'False) ((((C1 ('MetaCons "Mentioned" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Subscribed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unsubscribed" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Referenced" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Merged" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Assigned" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Closed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Reopened" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ActorUnassigned" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Labeled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unlabeled" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Milestoned" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Demilestoned" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Renamed" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Locked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unlocked" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HeadRefDeleted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeadRefRestored" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ReviewRequested" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReviewDismissed" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ReviewRequestRemoved" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MarkedAsDuplicate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnmarkedAsDuplicate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AddedToProject" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MovedColumnsInProject" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RemovedFromProject" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConvertedNoteToIssue" 'PrefixI 'False) (U1 :: Type -> Type)))))) | |
data IssueEvent Source #
Issue event
Constructors
| IssueEvent | |
| Fields 
 | |