github-webhooks-0.16.0: Aeson instances for GitHub Webhook payloads.
Copyright(c) Cuedo Control Engineering 2017-2022
LicenseMIT
MaintainerKyle Van Berendonck <foss@cuedo.com.au>
Safe HaskellTrustworthy
LanguageHaskell2010

GitHub.Data.Webhooks.Payload

Description

This module contains types that represent GitHub webhook's payload contents.

Synopsis

Construction Types

newtype URL Source #

Represents an internet address that would be suitable to query for more information. The GitHub API only returns valid URLs.

Constructors

URL Text 

Instances

Instances details
Eq URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

Data URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: URL -> Constr #

dataTypeOf :: URL -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

compare :: URL -> URL -> Ordering #

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

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

(>) :: URL -> URL -> Bool #

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

max :: URL -> URL -> URL #

min :: URL -> URL -> URL #

Show URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep URL :: Type -> Type #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

FromJSON URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: URL -> () #

type Rep URL Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep URL = D1 ('MetaData "URL" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'True) (C1 ('MetaCons "URL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

getUrl :: URL -> Text Source #

Demote GitHub URL to Text.

data OwnerType Source #

Represents the owner of a repository, pull request or similar.

A bot is a "special type of user which takes actions on behalf of GitHub Apps". See also https://developer.github.com/v4/object/bot/

Instances

Instances details
Bounded OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Enum OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Eq OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: OwnerType -> Constr #

dataTypeOf :: OwnerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Read OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep OwnerType :: Type -> Type #

FromJSON OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: OwnerType -> () #

type Rep OwnerType Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep OwnerType = D1 ('MetaData "OwnerType" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "OwnerUser" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OwnerOrganization" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OwnerBot" 'PrefixI 'False) (U1 :: Type -> Type)))

Webhook Types

data HookIssue Source #

Represents the "issue" field in the IssueCommentEvent and IssueEvent payload.

Instances

Instances details
Eq HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookIssue -> Constr #

dataTypeOf :: HookIssue -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookIssue :: Type -> Type #

FromJSON HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookIssue -> () #

type Rep HookIssue Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

data HookRepository Source #

Represents the "repository" field in all types of payload.

Constructors

HookRepository 

Fields

Instances

Instances details
Eq HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookRepository -> Constr #

dataTypeOf :: HookRepository -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookRepository :: Type -> Type #

FromJSON HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookRepository -> () #

type Rep HookRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookRepository = D1 ('MetaData "HookRepository" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookRepository" 'PrefixI 'True) ((((((S1 ('MetaSel ('Just "whRepoId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whRepoNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whRepoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whRepoFullName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "whRepoOwner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either HookSimpleUser HookUser)) :*: S1 ('MetaSel ('Just "whRepoIsPrivate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "whRepoHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :*: (((S1 ('MetaSel ('Just "whRepoIsAFork") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "whRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoForksUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoKeysUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whRepoCollaboratorsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoTeamsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoHooksUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoIssueEventsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))) :*: ((((S1 ('MetaSel ('Just "whRepoEventsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoAssigneesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoBranchesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoTagsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whRepoBlobsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoGitTagsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoGitRefsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoTreesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: (((S1 ('MetaSel ('Just "whRepoStatusesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoLanguagesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoStargazersUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoContributorsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whRepoSubscribersUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoSubscriptionUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoCommitsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoGitCommitsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))) :*: (((((S1 ('MetaSel ('Just "whRepoCommentsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoIssueCommentsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoContentsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoCompareUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whRepoMergesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoArchiveUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoDownloadsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoIssuesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: (((S1 ('MetaSel ('Just "whRepoPullsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoMilestonesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoNotificationsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoLabelsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whRepoReleasesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "whRepoUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whRepoPushedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))))) :*: ((((S1 ('MetaSel ('Just "whRepoGitUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoSshUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoCloneUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whRepoSvnUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whRepoHomepage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "whRepoSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whRepoStargazersCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whRepoWatchersCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :*: (((S1 ('MetaSel ('Just "whRepoLanguage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whRepoHasIssues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "whRepoHasDownloads") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "whRepoHasWiki") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "whRepoHasPages") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "whRepoForkCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whRepoMirrorUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: (S1 ('MetaSel ('Just "whRepoOpenIssuesCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whRepoDefaultBranchName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))))))

data HookRepositorySimple Source #

Represents the "repositories_added" and "repositories_removed" field in the InstallationRepositoriesEvent payload.

Instances

Instances details
Eq HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookRepositorySimple -> Constr #

dataTypeOf :: HookRepositorySimple -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookRepositorySimple :: Type -> Type #

FromJSON HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookRepositorySimple -> () #

type Rep HookRepositorySimple Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookRepositorySimple = D1 ('MetaData "HookRepositorySimple" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookRepositorySimple" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whSimplRepoId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whSimplRepoNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whSimplRepoName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whSimplRepoFullName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whSimplRepoIsPrivate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))

data HookRepositoryLabel Source #

Represents the "label" field in the LabelEvent payload.

Instances

Instances details
Eq HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookRepositoryLabel -> Constr #

dataTypeOf :: HookRepositoryLabel -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookRepositoryLabel :: Type -> Type #

FromJSON HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookRepositoryLabel -> () #

type Rep HookRepositoryLabel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookRepositoryLabel = D1 ('MetaData "HookRepositoryLabel" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookRepositoryLabel" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whRepoLabelNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whRepoLabelUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whRepoLabelName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whRepoLabelColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data HookUser Source #

Represents the "user" field in all types of payload.

Instances

Instances details
Eq HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookUser -> Constr #

dataTypeOf :: HookUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookUser :: Type -> Type #

Methods

from :: HookUser -> Rep HookUser x #

to :: Rep HookUser x -> HookUser #

FromJSON HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookUser -> () #

type Rep HookUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookUser = D1 ('MetaData "HookUser" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookUser" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "whUserLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whUserId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whUserNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whUserAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whUserGravatarId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whUserUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whUserHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whUserFollowersUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whUserFollowingUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))) :*: (((S1 ('MetaSel ('Just "whUserGistsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whUserStarredUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whUserSubscriptionsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whUserOrganizationsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whUserReposUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whUserEventsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whUserReceivedEventsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whUserType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OwnerType) :*: S1 ('MetaSel ('Just "whUserIsAdminOfSite") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))))

data HookSimpleUser Source #

Instances

Instances details
Eq HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookSimpleUser -> Constr #

dataTypeOf :: HookSimpleUser -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookSimpleUser :: Type -> Type #

FromJSON HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookSimpleUser -> () #

type Rep HookSimpleUser Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookSimpleUser = D1 ('MetaData "HookSimpleUser" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookSimpleUser" 'PrefixI 'True) (S1 ('MetaSel ('Just "whSimplUserName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whSimplUserEmail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whSimplUserLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))

data HookOrganization Source #

Represents the "organization" field in all types of payload.

Instances

Instances details
Eq HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookOrganization -> Constr #

dataTypeOf :: HookOrganization -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookOrganization :: Type -> Type #

FromJSON HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookOrganization -> () #

type Rep HookOrganization Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookOrganization = D1 ('MetaData "HookOrganization" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookOrganization" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whOrgLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whOrgId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whOrgNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "whOrgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whOrgReposUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whOrgEventsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: ((S1 ('MetaSel ('Just "whOrgHooksUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: (S1 ('MetaSel ('Just "whOrgIssuesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "whOrgMembersUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: (S1 ('MetaSel ('Just "whOrgPublicMembersUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whOrgAvatarUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whOrgDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))))

data HookOrganizationInvitation Source #

Represents the "invitation" field in the OrganizationEvent payload.

Instances

Instances details
Eq HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookOrganizationInvitation -> Constr #

dataTypeOf :: HookOrganizationInvitation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookOrganizationInvitation :: Type -> Type #

FromJSON HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookOrganizationInvitation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookOrganizationInvitation = D1 ('MetaData "HookOrganizationInvitation" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookOrganizationInvitation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whOrgInvitationId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whOrgInvitationNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whOrgInvitationLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whOrgInvitationEmail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whOrgInvitationRole") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))

data HookOrganizationMembership Source #

Represents the "membership" field in the OrganizationEvent payload.

Instances

Instances details
Eq HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookOrganizationMembership -> Constr #

dataTypeOf :: HookOrganizationMembership -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookOrganizationMembership :: Type -> Type #

FromJSON HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookOrganizationMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookOrganizationMembership = D1 ('MetaData "HookOrganizationMembership" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookOrganizationMembership" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whOrgMembershipUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whOrgMembershipState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whOrgMembershipRole") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whOrgMembershipOrgUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whOrgMembershipUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser)))))

data HookTeam Source #

Represents the "team" field in the TeamEvent and TeamAddEvent payload.

Instances

Instances details
Eq HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookTeam -> Constr #

dataTypeOf :: HookTeam -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookTeam :: Type -> Type #

Methods

from :: HookTeam -> Rep HookTeam x #

to :: Rep HookTeam x -> HookTeam #

FromJSON HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookTeam -> () #

type Rep HookTeam Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookTeam = D1 ('MetaData "HookTeam" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookTeam" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whTeamName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whTeamId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whTeamNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whTeamSlug") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "whTeamPermission") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whTeamUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whTeamMembersUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whTeamRepositoriesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))

data HookMarketplaceAccount Source #

Represents the "account" field in the HookMarketplacePurchase payload.

Instances

Instances details
Eq HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMarketplaceAccount -> Constr #

dataTypeOf :: HookMarketplaceAccount -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMarketplaceAccount :: Type -> Type #

FromJSON HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookMarketplaceAccount -> () #

type Rep HookMarketplaceAccount Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplaceAccount = D1 ('MetaData "HookMarketplaceAccount" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookMarketplaceAccount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whMarketplaceAccountType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 OwnerType) :*: S1 ('MetaSel ('Just "whMarketplaceAccountId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whMarketplaceAccountNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whMarketplaceAccountLogin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whMarketplaceAccountOrganizationBillingEmail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))

data HookMarketplaceBillingCycle Source #

Represents the "billing_cycle" field in the HookMarketplacePurchase payload.

Constructors

HookMarketplaceBillingCycleYearly

Decodes from "yearly"

HookMarketplaceBillingCycleMonthly

Decodes from "monthly".

HookMarketplaceBillingCycleOther !Text

The result of decoding an unknown marketplace purchase billing cycle type

Instances

Instances details
Eq HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMarketplaceBillingCycle -> Constr #

dataTypeOf :: HookMarketplaceBillingCycle -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMarketplaceBillingCycle :: Type -> Type #

FromJSON HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplaceBillingCycle Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplaceBillingCycle = D1 ('MetaData "HookMarketplaceBillingCycle" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookMarketplaceBillingCycleYearly" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HookMarketplaceBillingCycleMonthly" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookMarketplaceBillingCycleOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data HookMarketplacePlan Source #

Represents the "plan" field in the HookMarketplacePurchase payload.

Instances

Instances details
Eq HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMarketplacePlan -> Constr #

dataTypeOf :: HookMarketplacePlan -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMarketplacePlan :: Type -> Type #

FromJSON HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookMarketplacePlan -> () #

type Rep HookMarketplacePlan Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplacePlan = D1 ('MetaData "HookMarketplacePlan" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookMarketplacePlan" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whMarketplacePlanId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whMarketplacePlanName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whMarketplacePlanDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whMarketplacePlanMonthlyPriceInCents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "whMarketplacePlanYearlyPriceInCents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whMarketplacePlanPriceModel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookMarketplacePlanPriceModel)) :*: (S1 ('MetaSel ('Just "whMarketplacePlanHasFreeTrial") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "whMarketplacePlanUnitName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whMarketplacePlanBullet") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector Text)))))))

data HookMarketplacePlanPriceModel Source #

Represents the "price_model" field in the HookMarketplacePlan payload.

Constructors

HookMarketplacePlanPriceModelFlatRate

Decodes from "flat-rate"

HookMarketplacePlanPriceModelPerUnit

Decodes from "per-unit".

HookMarketplacePlanPriceModelFree

Decodes from "free".

HookMarketplacePlanPriceModelOther !Text

The result of decoding an unknown marketplace plan price model

Instances

Instances details
Eq HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMarketplacePlanPriceModel -> Constr #

dataTypeOf :: HookMarketplacePlanPriceModel -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMarketplacePlanPriceModel :: Type -> Type #

FromJSON HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplacePlanPriceModel Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplacePlanPriceModel = D1 ('MetaData "HookMarketplacePlanPriceModel" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) ((C1 ('MetaCons "HookMarketplacePlanPriceModelFlatRate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookMarketplacePlanPriceModelPerUnit" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookMarketplacePlanPriceModelFree" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookMarketplacePlanPriceModelOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data HookMarketplacePurchase Source #

Represents the "marketplace_purchase" field in the MarketplacePurchaseEvent payload.

Instances

Instances details
Eq HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMarketplacePurchase -> Constr #

dataTypeOf :: HookMarketplacePurchase -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMarketplacePurchase :: Type -> Type #

FromJSON HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookMarketplacePurchase -> () #

type Rep HookMarketplacePurchase Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookMarketplacePurchase = D1 ('MetaData "HookMarketplacePurchase" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookMarketplacePurchase" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whMarketplacePurchaseAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookMarketplaceAccount) :*: (S1 ('MetaSel ('Just "whMarketplacePurchaseBillingCycle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookMarketplaceBillingCycle)) :*: S1 ('MetaSel ('Just "whMarketplacePurchaseUnitCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "whMarketplacePurchaseOnFreeTrial") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "whMarketplacePurchaseFreeTrialEndsOn") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))) :*: (S1 ('MetaSel ('Just "whMarketplacePurchaseNextBillingDate") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "whMarketplacePurchasePlan") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookMarketplacePlan)))))

data HookMilestone Source #

Represents the "milestone" field in the MilestoneEvent payload.

Instances

Instances details
Eq HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMilestone -> Constr #

dataTypeOf :: HookMilestone -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMilestone :: Type -> Type #

FromJSON HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookMilestone -> () #

type Rep HookMilestone Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

data HookMembership Source #

Constructors

HookMembership 

Fields

Instances

Instances details
Eq HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookMembership -> Constr #

dataTypeOf :: HookMembership -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookMembership :: Type -> Type #

FromJSON HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookMembership -> () #

type Rep HookMembership Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

data HookProject Source #

Represents the "project" field in the ProjectEvent payload.

Instances

Instances details
Eq HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookProject -> Constr #

dataTypeOf :: HookProject -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookProject :: Type -> Type #

FromJSON HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookProject -> () #

type Rep HookProject Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

data HookProjectCard Source #

Represents the "project_card" field in the ProjectCardEvent payload.

Instances

Instances details
Eq HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookProjectCard -> Constr #

dataTypeOf :: HookProjectCard -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookProjectCard :: Type -> Type #

FromJSON HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookProjectCard -> () #

type Rep HookProjectCard Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookProjectCard = D1 ('MetaData "HookProjectCard" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookProjectCard" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whProjectCardUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whProjectCardColumnUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whProjectCardColumnId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "whProjectCardId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whProjectCardNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :*: ((S1 ('MetaSel ('Just "whProjectCardNote") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whProjectCardCreator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser)) :*: (S1 ('MetaSel ('Just "whProjectCardCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "whProjectCardUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whProjectCardContentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))))

data HookProjectColumn Source #

Represents the "project_column" field in the ProjectColumnEvent payload.

Instances

Instances details
Eq HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookProjectColumn -> Constr #

dataTypeOf :: HookProjectColumn -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookProjectColumn :: Type -> Type #

FromJSON HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookProjectColumn -> () #

type Rep HookProjectColumn Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookProjectColumn = D1 ('MetaData "HookProjectColumn" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookProjectColumn" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whProjectColumnUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whProjectColumnProjUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whProjectColumnCardsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whProjectColumnId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "whProjectColumnNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whProjectColumnName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whProjectColumnCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whProjectColumnUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)))))

data HookIssueLabels Source #

Represents the "issue.labels" field in the IssueCommentEvent and IssueEvent payloads.

Constructors

HookIssueLabels 

Fields

Instances

Instances details
Eq HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookIssueLabels -> Constr #

dataTypeOf :: HookIssueLabels -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookIssueLabels :: Type -> Type #

FromJSON HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookIssueLabels -> () #

type Rep HookIssueLabels Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookIssueLabels = D1 ('MetaData "HookIssueLabels" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookIssueLabels" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whIssueLabelId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "whIssueLabelNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whIssueLabelUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: (S1 ('MetaSel ('Just "whIssueLabelName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whIssueLabelColor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whIssueLabelIsDefault") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))

data HookCommit Source #

Constructors

HookCommit 

Fields

Instances

Instances details
Eq HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCommit -> Constr #

dataTypeOf :: HookCommit -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCommit :: Type -> Type #

FromJSON HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCommit -> () #

type Rep HookCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCommit = D1 ('MetaData "HookCommit" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookCommit" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whCommitSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whCommitUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whCommitHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)))) :*: (S1 ('MetaSel ('Just "whCommitCommentsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: (S1 ('MetaSel ('Just "whCommitAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either HookSimpleUser HookUser)) :*: S1 ('MetaSel ('Just "whCommitCommitter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Either HookSimpleUser HookUser))))))

data HookCheckSuiteStatus Source #

Represents the "status" field in the HookCheckSuite payload.

Constructors

HookCheckSuiteStatusRequested

Decodes from "requested"

HookCheckSuiteStatusQueued

Decodes from "queued".

HookCheckSuiteStatusInProgress

Decodes from "in_progress"

HookCheckSuiteStatusCompleted

Decodes from "completed"

HookCheckSuiteStatusOther !Text

The result of decoding an unknown check suite status type

Instances

Instances details
Eq HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckSuiteStatus -> Constr #

dataTypeOf :: HookCheckSuiteStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckSuiteStatus :: Type -> Type #

FromJSON HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckSuiteStatus -> () #

type Rep HookCheckSuiteStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckSuiteStatus = D1 ('MetaData "HookCheckSuiteStatus" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) ((C1 ('MetaCons "HookCheckSuiteStatusRequested" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckSuiteStatusQueued" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookCheckSuiteStatusInProgress" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HookCheckSuiteStatusCompleted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckSuiteStatusOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))

data HookCheckSuiteConclusion Source #

Represents the "conclusion" field in the HookCheckSuite payload.

Constructors

HookCheckSuiteConclusionSuccess

Decodes from "success"

HookCheckSuiteConclusionFailure

Decodes from "failure"

HookCheckSuiteConclusionNeutral

Decodes from "neutral"

HookCheckSuiteConclusionCancelled

Decodes from "cancelled"

HookCheckSuiteConclusionTimedOut

Decodes from "timed_out"

HookCheckSuiteConclusionActionRequired

Decodes from "action_required"

HookCheckSuiteConclusionStale

Decodes from "stale"

HookCheckSuiteConclusionOther !Text

The result of decoding an unknown check suite conclusion type

Instances

Instances details
Eq HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckSuiteConclusion -> Constr #

dataTypeOf :: HookCheckSuiteConclusion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckSuiteConclusion :: Type -> Type #

FromJSON HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckSuiteConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckSuiteConclusion = D1 ('MetaData "HookCheckSuiteConclusion" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (((C1 ('MetaCons "HookCheckSuiteConclusionSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckSuiteConclusionFailure" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookCheckSuiteConclusionNeutral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckSuiteConclusionCancelled" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HookCheckSuiteConclusionTimedOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckSuiteConclusionActionRequired" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookCheckSuiteConclusionStale" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckSuiteConclusionOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))

data HookCheckSuite Source #

Represents the "check_suite" field in the CheckSuiteEvent payload.

Constructors

HookCheckSuite 

Fields

Instances

Instances details
Eq HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckSuite -> Constr #

dataTypeOf :: HookCheckSuite -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckSuite :: Type -> Type #

FromJSON HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckSuite -> () #

type Rep HookCheckSuite Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckSuite = D1 ('MetaData "HookCheckSuite" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookCheckSuite" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whCheckSuiteId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "whCheckSuiteNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whCheckSuiteHeadBranch") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "whCheckSuiteHeadSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whCheckSuiteStatus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookCheckSuiteStatus)) :*: (S1 ('MetaSel ('Just "whCheckSuiteConclusion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookCheckSuiteConclusion)) :*: S1 ('MetaSel ('Just "whCheckSuiteUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: (((S1 ('MetaSel ('Just "whCheckSuiteBeforeSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whCheckSuiteAfterSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "whCheckSuitePullRequests") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector HookChecksPullRequest)) :*: S1 ('MetaSel ('Just "whCheckSuiteCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))) :*: ((S1 ('MetaSel ('Just "whCheckSuiteUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whCheckSuiteLatestCheckRunsCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "whCheckSuiteCheckRunsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "whCheckSuiteHeadCommit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookCheckSuiteCommit)))))))

data HookCheckSuiteCommit Source #

Represents the "head_commit" field in the CheckSuiteEvent payload.

Instances

Instances details
Eq HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckSuiteCommit -> Constr #

dataTypeOf :: HookCheckSuiteCommit -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckSuiteCommit :: Type -> Type #

FromJSON HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckSuiteCommit -> () #

type Rep HookCheckSuiteCommit Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckSuiteCommit = D1 ('MetaData "HookCheckSuiteCommit" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookCheckSuiteCommit" 'PrefixI 'True) (S1 ('MetaSel ('Just "whCheckSuiteCommitSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whCheckSuiteCommitAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookSimpleUser) :*: S1 ('MetaSel ('Just "whCheckSuiteCommitCommitter") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookSimpleUser))))

data HookCheckRunStatus Source #

Represents the "status" field in the HookCheckRun payload.

Constructors

HookCheckRunStatusQueued

Decodes from "queued"

HookCheckRunStatusInProgress

Decodes from "in_progress"

HookCheckRunStatusCompleted

Decodes from "completed"

HookCheckRunStatusOther !Text

The result of decoding an unknown check run status type

Instances

Instances details
Eq HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckRunStatus -> Constr #

dataTypeOf :: HookCheckRunStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckRunStatus :: Type -> Type #

FromJSON HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckRunStatus -> () #

type Rep HookCheckRunStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckRunStatus = D1 ('MetaData "HookCheckRunStatus" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) ((C1 ('MetaCons "HookCheckRunStatusQueued" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckRunStatusInProgress" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookCheckRunStatusCompleted" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckRunStatusOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data HookCheckRunConclusion Source #

Represents the "conclusion" field in the HookCheckRun payload.

Constructors

HookCheckRunConclusionSuccess

Decodes from "success"

HookCheckRunConclusionFailure

Decodes from "failure"

HookCheckRunConclusionNeutral

Decodes from "neutral"

HookCheckRunConclusionCancelled

Decodes from "cancelled"

HookCheckRunConclusionTimedOut

Decodes from "timed_out"

HookCheckRunConclusionActionRequired

Decodes from "action_required"

HookCheckRunConclusionStale

Decodes from "stale"

HookCheckRunConclusionOther !Text

The result of decoding an unknown check run conclusion type

Instances

Instances details
Eq HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckRunConclusion -> Constr #

dataTypeOf :: HookCheckRunConclusion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Show HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckRunConclusion :: Type -> Type #

FromJSON HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckRunConclusion -> () #

type Rep HookCheckRunConclusion Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckRunConclusion = D1 ('MetaData "HookCheckRunConclusion" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (((C1 ('MetaCons "HookCheckRunConclusionSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckRunConclusionFailure" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookCheckRunConclusionNeutral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckRunConclusionCancelled" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HookCheckRunConclusionTimedOut" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckRunConclusionActionRequired" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HookCheckRunConclusionStale" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HookCheckRunConclusionOther" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))

data HookCheckRun Source #

Represents the "check_run" field in the CheckRunEvent payload.

Instances

Instances details
Eq HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckRun -> Constr #

dataTypeOf :: HookCheckRun -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckRun :: Type -> Type #

FromJSON HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckRun -> () #

type Rep HookCheckRun Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckRun = D1 ('MetaData "HookCheckRun" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookCheckRun" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whCheckRunId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "whCheckRunNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whCheckRunHeadSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "whCheckRunExternalId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whCheckRunUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whCheckRunHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whCheckRunDetailsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: (((S1 ('MetaSel ('Just "whCheckRunStatus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookCheckRunStatus) :*: S1 ('MetaSel ('Just "whCheckRunConclusion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookCheckRunConclusion))) :*: (S1 ('MetaSel ('Just "whCheckRunStartedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whCheckRunCompletedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)))) :*: ((S1 ('MetaSel ('Just "whCheckRunOutput") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookCheckRunOutput) :*: S1 ('MetaSel ('Just "whCheckRunName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whCheckRunCheckSuite") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookCheckSuite) :*: S1 ('MetaSel ('Just "whCheckRunPullRequests") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector HookChecksPullRequest)))))))

data HookCheckRunOutput Source #

Represents the "output" field in the HookCheckRun payload.

Instances

Instances details
Eq HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckRunOutput -> Constr #

dataTypeOf :: HookCheckRunOutput -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckRunOutput :: Type -> Type #

FromJSON HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCheckRunOutput -> () #

type Rep HookCheckRunOutput Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckRunOutput = D1 ('MetaData "HookCheckRunOutput" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookCheckRunOutput" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whCheckRunOutputTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whCheckRunOutputSummary") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "whCheckRunOutputText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "whCheckRunOutputAnnotationsCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whCheckRunOutputAnnotationsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))

newtype HookCheckRunRequestedAction Source #

Represents the "requested_action" field in the CheckRunEvent payload.

Instances

Instances details
Eq HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCheckRunRequestedAction -> Constr #

dataTypeOf :: HookCheckRunRequestedAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCheckRunRequestedAction :: Type -> Type #

FromJSON HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckRunRequestedAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCheckRunRequestedAction = D1 ('MetaData "HookCheckRunRequestedAction" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'True) (C1 ('MetaCons "HookCheckRunRequestedAction" 'PrefixI 'True) (S1 ('MetaSel ('Just "whCheckRunRequestedActionIdentifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data HookChecksInstallation Source #

Represents the "installation" field in the checks payloads.

Instances

Instances details
Eq HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookChecksInstallation -> Constr #

dataTypeOf :: HookChecksInstallation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookChecksInstallation :: Type -> Type #

FromJSON HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookChecksInstallation -> () #

type Rep HookChecksInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookChecksInstallation = D1 ('MetaData "HookChecksInstallation" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookChecksInstallation" 'PrefixI 'True) (S1 ('MetaSel ('Just "whChecksInstallationId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "whChecksInstallationNodeId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data HookChecksPullRequest Source #

Represents the "pull_requests" field in the checks payloads.

Instances

Instances details
Eq HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookChecksPullRequest -> Constr #

dataTypeOf :: HookChecksPullRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookChecksPullRequest :: Type -> Type #

FromJSON HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookChecksPullRequest -> () #

type Rep HookChecksPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookChecksPullRequest = D1 ('MetaData "HookChecksPullRequest" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookChecksPullRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whChecksPullRequestUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whChecksPullRequestId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whChecksPullRequestNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "whChecksPullRequestHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookChecksPullRequestTarget) :*: S1 ('MetaSel ('Just "whChecksPullRequestBase") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookChecksPullRequestTarget)))))

data HookChecksPullRequestRepository Source #

Represents the "repo" field in the checks pull_request payloads.

Instances

Instances details
Eq HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookChecksPullRequestRepository -> Constr #

dataTypeOf :: HookChecksPullRequestRepository -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookChecksPullRequestRepository :: Type -> Type #

FromJSON HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookChecksPullRequestRepository Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookChecksPullRequestRepository = D1 ('MetaData "HookChecksPullRequestRepository" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookChecksPullRequestRepository" 'PrefixI 'True) (S1 ('MetaSel ('Just "whChecksPullRequestRepositoryId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "whChecksPullRequestRepositoryUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whChecksPullRequestRepositoryName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))

data HookChecksPullRequestTarget Source #

Represents the repo targets in the checks pull requests repository payloads.

Instances

Instances details
Eq HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookChecksPullRequestTarget -> Constr #

dataTypeOf :: HookChecksPullRequestTarget -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookChecksPullRequestTarget :: Type -> Type #

FromJSON HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookChecksPullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookChecksPullRequestTarget = D1 ('MetaData "HookChecksPullRequestTarget" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookChecksPullRequestTarget" 'PrefixI 'True) (S1 ('MetaSel ('Just "whChecksPullRequestTargetSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whChecksPullRequestTargetRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whChecksPullRequestTargetRepo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookChecksPullRequestRepository))))

data HookRelease Source #

Instances

Instances details
Eq HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookRelease -> Constr #

dataTypeOf :: HookRelease -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookRelease :: Type -> Type #

FromJSON HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookRelease -> () #

type Rep HookRelease Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookRelease = D1 ('MetaData "HookRelease" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookRelease" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "whReleaseUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whReleaseAssetsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whReleaseUploadUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whReleaseHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whReleaseId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whReleaseNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whReleaseTagName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whReleaseTargetCommitish") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :*: (((S1 ('MetaSel ('Just "whReleaseName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whReleaseIsDraft") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "whReleaseAuthor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser) :*: S1 ('MetaSel ('Just "whReleaseIsPreRelease") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "whReleaseCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whReleasePublishedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))) :*: (S1 ('MetaSel ('Just "whReleaseTarballUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whReleaseZipballUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whReleaseBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text))))))))

data HookPullRequest Source #

Instances

Instances details
Eq HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookPullRequest -> Constr #

dataTypeOf :: HookPullRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookPullRequest :: Type -> Type #

FromJSON HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookPullRequest -> () #

type Rep HookPullRequest Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookPullRequest = D1 ('MetaData "HookPullRequest" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookPullRequest" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "whPullReqUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whPullReqNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whPullReqDiffUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqPatchUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whPullReqIssueUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :*: (((S1 ('MetaSel ('Just "whPullReqState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqIsLocked") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "whPullReqTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser))) :*: ((S1 ('MetaSel ('Just "whPullReqBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "whPullReqUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "whPullReqClosedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime)) :*: S1 ('MetaSel ('Just "whPullReqMergedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe UTCTime))))))) :*: ((((S1 ('MetaSel ('Just "whPullReqMergeCommitSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whPullReqAssignee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookUser))) :*: (S1 ('MetaSel ('Just "whPullReqMilestone") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookMilestone)) :*: S1 ('MetaSel ('Just "whPullReqCommitsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))) :*: ((S1 ('MetaSel ('Just "whPullReqRevCommentsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqRevCommentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whPullReqCommentsUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqStatusesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))) :*: (((S1 ('MetaSel ('Just "whPullReqBase") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PullRequestTarget) :*: S1 ('MetaSel ('Just "whPullReqHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PullRequestTarget)) :*: (S1 ('MetaSel ('Just "whPullReqMergeableState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whPullReqCommentCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "whPullReqRevCommentCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "whPullReqCommitCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "whPullReqAdditionsCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "whPullReqDeletionsCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "whPullReqFileChangeCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))))))))

data PullRequestTarget Source #

Instances

Instances details
Eq PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: PullRequestTarget -> Constr #

dataTypeOf :: PullRequestTarget -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep PullRequestTarget :: Type -> Type #

FromJSON PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: PullRequestTarget -> () #

type Rep PullRequestTarget Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep PullRequestTarget = D1 ('MetaData "PullRequestTarget" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "PullRequestTarget" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whPullReqTargetSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqTargetUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser)) :*: (S1 ('MetaSel ('Just "whPullReqTargetRepo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe HookRepository)) :*: (S1 ('MetaSel ('Just "whPullReqTargetLabel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqTargetRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))))

data HookPullRequestReview Source #

Represents the "pull_request" field in the PullRequestReviewEvent payload.

Instances

Instances details
Eq HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookPullRequestReview -> Constr #

dataTypeOf :: HookPullRequestReview -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookPullRequestReview :: Type -> Type #

FromJSON HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookPullRequestReview -> () #

type Rep HookPullRequestReview Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookPullRequestReview = D1 ('MetaData "HookPullRequestReview" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookPullRequestReview" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whPullReqReviewId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whPullReqReviewNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whPullReqReviewUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser) :*: S1 ('MetaSel ('Just "whPullReqReviewBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "whPullReqReviewSubmittedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whPullReqReviewState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whPullReqReviewHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqReviewPullUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))

data HookInstallation Source #

Represents the "installation" field in the InstallationEvent payload.

Instances

Instances details
Eq HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookInstallation -> Constr #

dataTypeOf :: HookInstallation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookInstallation :: Type -> Type #

FromJSON HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookInstallation -> () #

type Rep HookInstallation Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookInstallation = D1 ('MetaData "HookInstallation" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookInstallation" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whInstallationId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whInstallationAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser)) :*: (S1 ('MetaSel ('Just "whInstallationRepoSel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whInstallationTokenUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whInstallationRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)))))

data HookDeployment Source #

Represents the "deployment" field in the DeploymentEvent and DeploymentStatusEvent payload.

Instances

Instances details
Eq HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookDeployment -> Constr #

dataTypeOf :: HookDeployment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookDeployment :: Type -> Type #

FromJSON HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookDeployment -> () #

type Rep HookDeployment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookDeployment = D1 ('MetaData "HookDeployment" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookDeployment" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whDeploymentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whDeploymentId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whDeploymentNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "whDeploymentSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whDeploymentRef") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whDeploymentTask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :*: ((S1 ('MetaSel ('Just "whDeploymentEnv") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whDeploymentDescription") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whDeploymentCreator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser))) :*: ((S1 ('MetaSel ('Just "whDeploymentCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whDeploymentUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "whDeploymentStatusesUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whDeploymentRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))))

data HookDeploymentStatus Source #

Represents the "deployment_status" field in the DeploymentStatusEvent payload.

Instances

Instances details
Eq HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookDeploymentStatus -> Constr #

dataTypeOf :: HookDeploymentStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookDeploymentStatus :: Type -> Type #

FromJSON HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookDeploymentStatus -> () #

type Rep HookDeploymentStatus Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookDeploymentStatus = D1 ('MetaData "HookDeploymentStatus" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookDeploymentStatus" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whDeploymentStatusUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whDeploymentStatusId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whDeploymentStatusNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whDeploymentStatusState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whDeploymentStatusCreator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser)))) :*: ((S1 ('MetaSel ('Just "whDeploymentStatusDesc") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "whDeploymentStatusTargetUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe URL)) :*: S1 ('MetaSel ('Just "whDeploymentStatusCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))) :*: (S1 ('MetaSel ('Just "whDeploymentStatusUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "whDeploymentStatusDeplUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whDeploymentStatusRepoUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))))

data HookWikiPage Source #

Represents the "pages" field in the GollumEvent payload.

Instances

Instances details
Eq HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookWikiPage -> Constr #

dataTypeOf :: HookWikiPage -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookWikiPage :: Type -> Type #

FromJSON HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookWikiPage -> () #

type Rep HookWikiPage Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookWikiPage = D1 ('MetaData "HookWikiPage" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookWikiPage" 'PrefixI 'True) ((S1 ('MetaSel ('Just "whWikiPageName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whWikiPageTitle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whWikiPageSummary") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "wkWikiPageAction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whWikiPageSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whWikiPageHtmlUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 URL)))))

data HookPageBuildResult Source #

Represents the "build" field in the PageBuildEvent payload.

Instances

Instances details
Eq HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookPageBuildResult -> Constr #

dataTypeOf :: HookPageBuildResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookPageBuildResult :: Type -> Type #

FromJSON HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookPageBuildResult -> () #

type Rep HookPageBuildResult Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookPageBuildResult = D1 ('MetaData "HookPageBuildResult" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookPageBuildResult" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whPageBuildUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPageBuildStatus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whPageBuildError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whPageBuildPusher") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser))) :*: ((S1 ('MetaSel ('Just "whPageBuildCommitSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPageBuildDuration") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "whPageBuildCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whPageBuildUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)))))

data HookIssueComment Source #

Represents the "issue" field in IssueComentEvent payload.

Instances

Instances details
Eq HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookIssueComment -> Constr #

dataTypeOf :: HookIssueComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookIssueComment :: Type -> Type #

FromJSON HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookIssueComment -> () #

type Rep HookIssueComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookIssueComment = D1 ('MetaData "HookIssueComment" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookIssueComment" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whIssueCommentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whIssueCommentHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "whIssueCommentIssueUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whIssueCommentId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: ((S1 ('MetaSel ('Just "whIssueCommentNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whIssueCommentUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser)) :*: (S1 ('MetaSel ('Just "whIssueCommentCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "whIssueCommentUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whIssueCommentBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))))

data HookCommitComment Source #

Represents the "comment" field in the CommitCommentEvent payload.

Instances

Instances details
Eq HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookCommitComment -> Constr #

dataTypeOf :: HookCommitComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookCommitComment :: Type -> Type #

FromJSON HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

rnf :: HookCommitComment -> () #

type Rep HookCommitComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookCommitComment = D1 ('MetaData "HookCommitComment" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookCommitComment" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whCommitCommentUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whCommitCommentHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whCommitCommentId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "whCommitCommentNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "whCommitCommentUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser) :*: S1 ('MetaSel ('Just "whCommitCommentPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))) :*: ((S1 ('MetaSel ('Just "whCommitCommentLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "whCommitCommentPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "whCommitCommentCommitSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "whCommitCommentCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "whCommitCommentUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whCommitCommentBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))))))

data HookPullRequestReviewComment Source #

Represents the "pull_request" field in the PullRequestReviewCommentEvent payload.

Instances

Instances details
Eq HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Data HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Methods

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

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

toConstr :: HookPullRequestReviewComment -> Constr #

dataTypeOf :: HookPullRequestReviewComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Generic HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

Associated Types

type Rep HookPullRequestReviewComment :: Type -> Type #

FromJSON HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

NFData HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookPullRequestReviewComment Source # 
Instance details

Defined in GitHub.Data.Webhooks.Payload

type Rep HookPullRequestReviewComment = D1 ('MetaData "HookPullRequestReviewComment" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.16.0-GQG1gFd2xAu72cfoEHIbGV" 'False) (C1 ('MetaCons "HookPullRequestReviewComment" 'PrefixI 'True) (((S1 ('MetaSel ('Just "whPullReqRevComUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: (S1 ('MetaSel ('Just "whPullReqRevComId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whPullReqRevComNodeId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "whPullReqRevComDiffHunk") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqRevComPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whPullReqRevComPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "whPullReqRevComOrigPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))) :*: (((S1 ('MetaSel ('Just "whPullReqRevComCommitSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "whPullReqRevComOrigSha") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "whPullReqRevComUser") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HookUser) :*: S1 ('MetaSel ('Just "whPullReqRevComBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :*: ((S1 ('MetaSel ('Just "whPullReqRevComCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "whPullReqRevComUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime)) :*: (S1 ('MetaSel ('Just "whPullReqRevComHtmlUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "whPullReqRevComPullReqUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL))))))