github-webhooks-0.10.0: Aeson instances for GitHub Webhook payloads.

Copyright(c) OnRock Engineering 2018
LicenseMIT
MaintainerKyle Van Berendonck <foss@onrock.engineering>
Safe HaskellTrustworthy
LanguageHaskell2010

GitHub.Data.Webhooks.Payload

Contents

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

Eq URL Source # 

Methods

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

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

Data URL Source # 

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

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 # 

Methods

showsPrec :: Int -> URL -> ShowS #

show :: URL -> String #

showList :: [URL] -> ShowS #

Generic URL Source # 

Associated Types

type Rep URL :: * -> * #

Methods

from :: URL -> Rep URL x #

to :: Rep URL x -> URL #

FromJSON URL Source # 
NFData URL Source # 

Methods

rnf :: URL -> () #

type Rep URL Source # 
type Rep URL = D1 * (MetaData "URL" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" True) (C1 * (MetaCons "URL" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))

getUrl :: URL -> Text Source #

Demote GitHub URL to Text.

data OwnerType Source #

Represents the owner of the repository.

Instances

Bounded OwnerType Source # 
Enum OwnerType Source # 
Eq OwnerType Source # 
Data OwnerType Source # 

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 :: (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 # 
Read OwnerType Source # 
Show OwnerType Source # 
Generic OwnerType Source # 

Associated Types

type Rep OwnerType :: * -> * #

FromJSON OwnerType Source # 
NFData OwnerType Source # 

Methods

rnf :: OwnerType -> () #

type Rep OwnerType Source # 
type Rep OwnerType = D1 * (MetaData "OwnerType" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" False) ((:+:) * (C1 * (MetaCons "OwnerUser" PrefixI False) (U1 *)) (C1 * (MetaCons "OwnerOrganization" PrefixI False) (U1 *)))

Webhook Types

data HookIssue Source #

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

Instances

Eq HookIssue Source # 
Data HookIssue Source # 

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 :: (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 # 
Generic HookIssue Source # 

Associated Types

type Rep HookIssue :: * -> * #

FromJSON HookIssue Source # 
NFData HookIssue Source # 

Methods

rnf :: HookIssue -> () #

type Rep HookIssue Source # 

data HookRepository Source #

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

Constructors

HookRepository 

Fields

Instances

Eq HookRepository Source # 
Data HookRepository Source # 

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 :: (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 # 
Generic HookRepository Source # 

Associated Types

type Rep HookRepository :: * -> * #

FromJSON HookRepository Source # 
NFData HookRepository Source # 

Methods

rnf :: HookRepository -> () #

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

data HookRepositorySimple Source #

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

Instances

Eq HookRepositorySimple Source # 
Data HookRepositorySimple Source # 

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 :: (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 # 
Generic HookRepositorySimple Source # 
FromJSON HookRepositorySimple Source # 
NFData HookRepositorySimple Source # 

Methods

rnf :: HookRepositorySimple -> () #

type Rep HookRepositorySimple Source # 
type Rep HookRepositorySimple = D1 * (MetaData "HookRepositorySimple" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" False) (C1 * (MetaCons "HookRepositorySimple" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "whSimplRepoId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "whSimplRepoName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "whSimplRepoFullName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

data HookRepositoryLabel Source #

Represents the "label" field in the LabelEvent payload.

Instances

Eq HookRepositoryLabel Source # 
Data HookRepositoryLabel Source # 

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 :: (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 # 
Generic HookRepositoryLabel Source # 
FromJSON HookRepositoryLabel Source # 
NFData HookRepositoryLabel Source # 

Methods

rnf :: HookRepositoryLabel -> () #

type Rep HookRepositoryLabel Source # 
type Rep HookRepositoryLabel = D1 * (MetaData "HookRepositoryLabel" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" False) (C1 * (MetaCons "HookRepositoryLabel" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "whRepoLabelUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) ((:*:) * (S1 * (MetaSel (Just Symbol "whRepoLabelName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "whRepoLabelColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

data HookUser Source #

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

Instances

Eq HookUser Source # 
Data HookUser Source # 

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 :: (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 # 
Generic HookUser Source # 

Associated Types

type Rep HookUser :: * -> * #

Methods

from :: HookUser -> Rep HookUser x #

to :: Rep HookUser x -> HookUser #

FromJSON HookUser Source # 
NFData HookUser Source # 

Methods

rnf :: HookUser -> () #

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

data HookSimpleUser Source #

Instances

Eq HookSimpleUser Source # 
Data HookSimpleUser Source # 

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 :: (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 # 
Generic HookSimpleUser Source # 

Associated Types

type Rep HookSimpleUser :: * -> * #

FromJSON HookSimpleUser Source # 
NFData HookSimpleUser Source # 

Methods

rnf :: HookSimpleUser -> () #

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

data HookOrganization Source #

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

Instances

Eq HookOrganization Source # 
Data HookOrganization Source # 

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 :: (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 # 
Generic HookOrganization Source # 
FromJSON HookOrganization Source # 
NFData HookOrganization Source # 

Methods

rnf :: HookOrganization -> () #

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

data HookOrganizationInvitation Source #

Represents the "invitation" field in the OrganizationEvent payload.

Instances

Eq HookOrganizationInvitation Source # 
Data HookOrganizationInvitation Source # 

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 :: (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 # 
Generic HookOrganizationInvitation Source # 
FromJSON HookOrganizationInvitation Source # 
NFData HookOrganizationInvitation Source # 
type Rep HookOrganizationInvitation Source # 
type Rep HookOrganizationInvitation = D1 * (MetaData "HookOrganizationInvitation" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" False) (C1 * (MetaCons "HookOrganizationInvitation" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whOrgInvitationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "whOrgInvitationLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "whOrgInvitationEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "whOrgInvitationRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))))

data HookOrganizationMembership Source #

Represents the "membership" field in the OrganizationEvent payload.

Instances

Eq HookOrganizationMembership Source # 
Data HookOrganizationMembership Source # 

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 :: (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 # 
Generic HookOrganizationMembership Source # 
FromJSON HookOrganizationMembership Source # 
NFData HookOrganizationMembership Source # 
type Rep HookOrganizationMembership Source # 
type Rep HookOrganizationMembership = D1 * (MetaData "HookOrganizationMembership" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" False) (C1 * (MetaCons "HookOrganizationMembership" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whOrgMembershipUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "whOrgMembershipState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "whOrgMembershipRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "whOrgMembershipOrgUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "whOrgMembershipUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser))))))

data HookTeam Source #

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

Instances

Eq HookTeam Source # 
Data HookTeam Source # 

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 :: (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 # 
Generic HookTeam Source # 

Associated Types

type Rep HookTeam :: * -> * #

Methods

from :: HookTeam -> Rep HookTeam x #

to :: Rep HookTeam x -> HookTeam #

FromJSON HookTeam Source # 
NFData HookTeam Source # 

Methods

rnf :: HookTeam -> () #

type Rep HookTeam Source # 

data HookMilestone Source #

Represents the "milestone" field in the MilestoneEvent payload.

Instances

Eq HookMilestone Source # 
Data HookMilestone Source # 

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 :: (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 # 
Generic HookMilestone Source # 

Associated Types

type Rep HookMilestone :: * -> * #

FromJSON HookMilestone Source # 
NFData HookMilestone Source # 

Methods

rnf :: HookMilestone -> () #

type Rep HookMilestone Source # 

data HookMembership Source #

Constructors

HookMembership 

Fields

Instances

Eq HookMembership Source # 
Data HookMembership Source # 

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 :: (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 # 
Generic HookMembership Source # 

Associated Types

type Rep HookMembership :: * -> * #

FromJSON HookMembership Source # 
NFData HookMembership Source # 

Methods

rnf :: HookMembership -> () #

type Rep HookMembership Source # 

data HookProject Source #

Represents the "project" field in the ProjectEvent payload.

Instances

Eq HookProject Source # 
Data HookProject Source # 

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 :: (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 # 
Generic HookProject Source # 

Associated Types

type Rep HookProject :: * -> * #

FromJSON HookProject Source # 
NFData HookProject Source # 

Methods

rnf :: HookProject -> () #

type Rep HookProject Source # 

data HookProjectCard Source #

Represents the "project_card" field in the ProjectCardEvent payload.

Instances

Eq HookProjectCard Source # 
Data HookProjectCard Source # 

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 :: (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 # 
Generic HookProjectCard Source # 
FromJSON HookProjectCard Source # 
NFData HookProjectCard Source # 

Methods

rnf :: HookProjectCard -> () #

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

data HookProjectColumn Source #

Represents the "project_column" field in the ProjectColumnEvent payload.

Instances

Eq HookProjectColumn Source # 
Data HookProjectColumn Source # 

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 :: (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 # 
Generic HookProjectColumn Source # 
FromJSON HookProjectColumn Source # 
NFData HookProjectColumn Source # 

Methods

rnf :: HookProjectColumn -> () #

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

data HookIssueLabels Source #

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

Constructors

HookIssueLabels 

Fields

Instances

Eq HookIssueLabels Source # 
Data HookIssueLabels Source # 

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 :: (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 # 
Generic HookIssueLabels Source # 
FromJSON HookIssueLabels Source # 
NFData HookIssueLabels Source # 

Methods

rnf :: HookIssueLabels -> () #

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

data HookCommit Source #

Constructors

HookCommit 

Fields

Instances

Eq HookCommit Source # 
Data HookCommit Source # 

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 :: (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 # 
Generic HookCommit Source # 

Associated Types

type Rep HookCommit :: * -> * #

FromJSON HookCommit Source # 
NFData HookCommit Source # 

Methods

rnf :: HookCommit -> () #

type Rep HookCommit Source # 

data HookRelease Source #

Instances

Eq HookRelease Source # 
Data HookRelease Source # 

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 :: (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 # 
Generic HookRelease Source # 

Associated Types

type Rep HookRelease :: * -> * #

FromJSON HookRelease Source # 
NFData HookRelease Source # 

Methods

rnf :: HookRelease -> () #

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

data HookPullRequest Source #

Instances

Eq HookPullRequest Source # 
Data HookPullRequest Source # 

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 :: (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 # 
Generic HookPullRequest Source # 
FromJSON HookPullRequest Source # 
NFData HookPullRequest Source # 

Methods

rnf :: HookPullRequest -> () #

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

data PullRequestTarget Source #

Instances

Eq PullRequestTarget Source # 
Data PullRequestTarget Source # 

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 :: (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 # 
Generic PullRequestTarget Source # 
FromJSON PullRequestTarget Source # 
NFData PullRequestTarget Source # 

Methods

rnf :: PullRequestTarget -> () #

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

data HookPullRequestReview Source #

Represents the "pull_request" field in the PullRequestReviewEvent payload.

Instances

Eq HookPullRequestReview Source # 
Data HookPullRequestReview Source # 

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 :: (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 # 
Generic HookPullRequestReview Source # 
FromJSON HookPullRequestReview Source # 
NFData HookPullRequestReview Source # 

Methods

rnf :: HookPullRequestReview -> () #

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

data HookInstallation Source #

Represents the "installation" field in the InstallationEvent payload.

Instances

Eq HookInstallation Source # 
Data HookInstallation Source # 

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 :: (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 # 
Generic HookInstallation Source # 
FromJSON HookInstallation Source # 
NFData HookInstallation Source # 

Methods

rnf :: HookInstallation -> () #

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

data HookDeployment Source #

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

Instances

Eq HookDeployment Source # 
Data HookDeployment Source # 

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 :: (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 # 
Generic HookDeployment Source # 

Associated Types

type Rep HookDeployment :: * -> * #

FromJSON HookDeployment Source # 
NFData HookDeployment Source # 

Methods

rnf :: HookDeployment -> () #

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

data HookDeploymentStatus Source #

Represents the "deployment_status" field in the DeploymentStatusEvent payload.

Instances

Eq HookDeploymentStatus Source # 
Data HookDeploymentStatus Source # 

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 :: (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 # 
Generic HookDeploymentStatus Source # 
FromJSON HookDeploymentStatus Source # 
NFData HookDeploymentStatus Source # 

Methods

rnf :: HookDeploymentStatus -> () #

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

data HookWikiPage Source #

Represents the "pages" field in the GollumEvent payload.

Instances

Eq HookWikiPage Source # 
Data HookWikiPage Source # 

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 :: (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 # 
Generic HookWikiPage Source # 

Associated Types

type Rep HookWikiPage :: * -> * #

FromJSON HookWikiPage Source # 
NFData HookWikiPage Source # 

Methods

rnf :: HookWikiPage -> () #

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

data HookPageBuildResult Source #

Represents the "build" field in the PageBuildEvent payload.

Instances

Eq HookPageBuildResult Source # 
Data HookPageBuildResult Source # 

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 :: (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 # 
Generic HookPageBuildResult Source # 
FromJSON HookPageBuildResult Source # 
NFData HookPageBuildResult Source # 

Methods

rnf :: HookPageBuildResult -> () #

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

data HookIssueComment Source #

Represents the "issue" field in IssueComentEvent payload.

Instances

Eq HookIssueComment Source # 
Data HookIssueComment Source # 

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 :: (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 # 
Generic HookIssueComment Source # 
FromJSON HookIssueComment Source # 
NFData HookIssueComment Source # 

Methods

rnf :: HookIssueComment -> () #

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

data HookCommitComment Source #

Represents the "comment" field in the CommitCommentEvent payload.

Instances

Eq HookCommitComment Source # 
Data HookCommitComment Source # 

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 :: (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 # 
Generic HookCommitComment Source # 
FromJSON HookCommitComment Source # 
NFData HookCommitComment Source # 

Methods

rnf :: HookCommitComment -> () #

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

data HookPullRequestReviewComment Source #

Represents the "pull_request" field in the PullRequestReviewCommentEvent payload.

Instances

Eq HookPullRequestReviewComment Source # 
Data HookPullRequestReviewComment Source # 

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 :: (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 # 
Generic HookPullRequestReviewComment Source # 
FromJSON HookPullRequestReviewComment Source # 
NFData HookPullRequestReviewComment Source # 
type Rep HookPullRequestReviewComment Source # 
type Rep HookPullRequestReviewComment = D1 * (MetaData "HookPullRequestReviewComment" "GitHub.Data.Webhooks.Payload" "github-webhooks-0.10.0-Dd0Gq8DLVu1A2wO5Wdcktt" False) (C1 * (MetaCons "HookPullRequestReviewComment" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "whPullReqRevComDiffHunk") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "whPullReqRevComPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))) ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComOrigPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "whPullReqRevComCommitSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComOrigSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser)) (S1 * (MetaSel (Just Symbol "whPullReqRevComBody") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)) (S1 * (MetaSel (Just Symbol "whPullReqRevComUpdatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime))) ((:*:) * (S1 * (MetaSel (Just Symbol "whPullReqRevComHtmlUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)) (S1 * (MetaSel (Just Symbol "whPullReqRevComPullReqUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * URL)))))))