github-0.23: Access to the GitHub API, v3.

LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Issues

Description

 
Synopsis

Documentation

data Issue Source #

Instances
Eq Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

(==) :: Issue -> Issue -> Bool #

(/=) :: Issue -> Issue -> Bool #

Data Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Issue -> c Issue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Issue #

toConstr :: Issue -> Constr #

dataTypeOf :: Issue -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Issue) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Issue) #

gmapT :: (forall b. Data b => b -> b) -> Issue -> Issue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Issue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Issue -> r #

gmapQ :: (forall d. Data d => d -> u) -> Issue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Issue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Issue -> m Issue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Issue -> m Issue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Issue -> m Issue #

Ord Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

compare :: Issue -> Issue -> Ordering #

(<) :: Issue -> Issue -> Bool #

(<=) :: Issue -> Issue -> Bool #

(>) :: Issue -> Issue -> Bool #

(>=) :: Issue -> Issue -> Bool #

max :: Issue -> Issue -> Issue #

min :: Issue -> Issue -> Issue #

Show Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

showsPrec :: Int -> Issue -> ShowS #

show :: Issue -> String #

showList :: [Issue] -> ShowS #

Generic Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Associated Types

type Rep Issue :: Type -> Type #

Methods

from :: Issue -> Rep Issue x #

to :: Rep Issue x -> Issue #

FromJSON Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Binary Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

put :: Issue -> Put #

get :: Get Issue #

putList :: [Issue] -> Put #

NFData Issue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

rnf :: Issue -> () #

type Rep Issue Source # 
Instance details

Defined in GitHub.Data.Issues

type Rep Issue = D1 (MetaData "Issue" "GitHub.Data.Issues" "github-0.23-11dKNrzUdUsEui3iNni5w1" False) (C1 (MetaCons "Issue" PrefixI True) ((((S1 (MetaSel (Just "issueClosedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 (MetaSel (Just "issueUpdatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)) :*: (S1 (MetaSel (Just "issueEventsUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL) :*: S1 (MetaSel (Just "issueHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe URL)))) :*: ((S1 (MetaSel (Just "issueClosedBy") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SimpleUser)) :*: S1 (MetaSel (Just "issueLabels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector IssueLabel))) :*: (S1 (MetaSel (Just "issueNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IssueNumber) :*: (S1 (MetaSel (Just "issueAssignees") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector SimpleUser)) :*: S1 (MetaSel (Just "issueUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SimpleUser))))) :*: (((S1 (MetaSel (Just "issueTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "issuePullRequest") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PullRequestReference))) :*: (S1 (MetaSel (Just "issueUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL) :*: S1 (MetaSel (Just "issueCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime))) :*: ((S1 (MetaSel (Just "issueBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "issueState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IssueState)) :*: (S1 (MetaSel (Just "issueId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Id Issue)) :*: (S1 (MetaSel (Just "issueComments") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "issueMilestone") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Milestone))))))))

data NewIssue Source #

Instances
Eq NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Data NewIssue Source # 
Instance details

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 :: (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 #

Ord NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Show NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Generic NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Associated Types

type Rep NewIssue :: Type -> Type #

Methods

from :: NewIssue -> Rep NewIssue x #

to :: Rep NewIssue x -> NewIssue #

ToJSON NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Binary NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

put :: NewIssue -> Put #

get :: Get NewIssue #

putList :: [NewIssue] -> Put #

NFData NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

rnf :: NewIssue -> () #

type Rep NewIssue Source # 
Instance details

Defined in GitHub.Data.Issues

type Rep NewIssue = D1 (MetaData "NewIssue" "GitHub.Data.Issues" "github-0.23-11dKNrzUdUsEui3iNni5w1" 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))))))))

data EditIssue Source #

Instances
Eq EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Data EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EditIssue -> c EditIssue #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EditIssue #

toConstr :: EditIssue -> Constr #

dataTypeOf :: EditIssue -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EditIssue) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EditIssue) #

gmapT :: (forall b. Data b => b -> b) -> EditIssue -> EditIssue #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EditIssue -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EditIssue -> r #

gmapQ :: (forall d. Data d => d -> u) -> EditIssue -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EditIssue -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EditIssue -> m EditIssue #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EditIssue -> m EditIssue #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EditIssue -> m EditIssue #

Ord EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Show EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Generic EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Associated Types

type Rep EditIssue :: Type -> Type #

ToJSON EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Binary EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

NFData EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

rnf :: EditIssue -> () #

type Rep EditIssue Source # 
Instance details

Defined in GitHub.Data.Issues

data IssueComment Source #

Instances
Eq IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Data IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IssueComment -> c IssueComment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IssueComment #

toConstr :: IssueComment -> Constr #

dataTypeOf :: IssueComment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IssueComment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IssueComment) #

gmapT :: (forall b. Data b => b -> b) -> IssueComment -> IssueComment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IssueComment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IssueComment -> r #

gmapQ :: (forall d. Data d => d -> u) -> IssueComment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IssueComment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IssueComment -> m IssueComment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IssueComment -> m IssueComment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IssueComment -> m IssueComment #

Ord IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Show IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Generic IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Associated Types

type Rep IssueComment :: Type -> Type #

FromJSON IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Binary IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

NFData IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

rnf :: IssueComment -> () #

type Rep IssueComment Source # 
Instance details

Defined in GitHub.Data.Issues

type Rep IssueComment = D1 (MetaData "IssueComment" "GitHub.Data.Issues" "github-0.23-11dKNrzUdUsEui3iNni5w1" False) (C1 (MetaCons "IssueComment" PrefixI True) ((S1 (MetaSel (Just "issueCommentUpdatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime) :*: (S1 (MetaSel (Just "issueCommentUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 SimpleUser) :*: S1 (MetaSel (Just "issueCommentUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL))) :*: ((S1 (MetaSel (Just "issueCommentHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL) :*: S1 (MetaSel (Just "issueCommentCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UTCTime)) :*: (S1 (MetaSel (Just "issueCommentBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "issueCommentId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))))

data EventType Source #

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
Bounded EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Enum EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Eq EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Data EventType Source # 
Instance details

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 :: (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 #

Ord EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Show EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Generic EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Associated Types

type Rep EventType :: Type -> Type #

FromJSON EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Binary EventType Source # 
Instance details

Defined in GitHub.Data.Issues

NFData EventType Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

rnf :: EventType -> () #

type Rep EventType Source # 
Instance details

Defined in GitHub.Data.Issues

type Rep EventType = D1 (MetaData "EventType" "GitHub.Data.Issues" "github-0.23-11dKNrzUdUsEui3iNni5w1" 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

Instances
Eq IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Data IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IssueEvent -> c IssueEvent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IssueEvent #

toConstr :: IssueEvent -> Constr #

dataTypeOf :: IssueEvent -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IssueEvent) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IssueEvent) #

gmapT :: (forall b. Data b => b -> b) -> IssueEvent -> IssueEvent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IssueEvent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IssueEvent -> r #

gmapQ :: (forall d. Data d => d -> u) -> IssueEvent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IssueEvent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IssueEvent -> m IssueEvent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IssueEvent -> m IssueEvent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IssueEvent -> m IssueEvent #

Ord IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Show IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Generic IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Associated Types

type Rep IssueEvent :: Type -> Type #

FromJSON IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Binary IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

NFData IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues

Methods

rnf :: IssueEvent -> () #

type Rep IssueEvent Source # 
Instance details

Defined in GitHub.Data.Issues