github-0.27: Access to the GitHub API, v3.
LicenseBSD-3-Clause
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

GitHub.Data.Webhooks

Description

 
Synopsis

Documentation

data RepoWebhook Source #

Instances

Instances details
Eq RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Data RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

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

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

toConstr :: RepoWebhook -> Constr #

dataTypeOf :: RepoWebhook -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Show RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Generic RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Associated Types

type Rep RepoWebhook :: Type -> Type #

FromJSON RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Binary RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

NFData RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

rnf :: RepoWebhook -> () #

type Rep RepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

type Rep RepoWebhook = D1 ('MetaData "RepoWebhook" "GitHub.Data.Webhooks" "github-0.27-E2VX4APYqInCeK2QmfbNoQ" 'False) (C1 ('MetaCons "RepoWebhook" 'PrefixI 'True) (((S1 ('MetaSel ('Just "repoWebhookUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL) :*: S1 ('MetaSel ('Just "repoWebhookTestUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 URL)) :*: (S1 ('MetaSel ('Just "repoWebhookId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id RepoWebhook)) :*: (S1 ('MetaSel ('Just "repoWebhookName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "repoWebhookActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "repoWebhookEvents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Vector RepoWebhookEvent)) :*: S1 ('MetaSel ('Just "repoWebhookConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Text Text))) :*: (S1 ('MetaSel ('Just "repoWebhookLastResponse") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoWebhookResponse) :*: (S1 ('MetaSel ('Just "repoWebhookUpdatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "repoWebhookCreatedAt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime))))))

data RepoWebhookEvent Source #

Instances

Instances details
Eq RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Data RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

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

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

toConstr :: RepoWebhookEvent -> Constr #

dataTypeOf :: RepoWebhookEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Show RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Generic RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Associated Types

type Rep RepoWebhookEvent :: Type -> Type #

ToJSON RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

FromJSON RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Binary RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

NFData RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

rnf :: RepoWebhookEvent -> () #

type Rep RepoWebhookEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

type Rep RepoWebhookEvent = D1 ('MetaData "RepoWebhookEvent" "GitHub.Data.Webhooks" "github-0.27-E2VX4APYqInCeK2QmfbNoQ" 'False) (((((C1 ('MetaCons "WebhookWildcardEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebhookCheckRunEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookCheckSuiteEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookCodeScanningAlert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookCommitCommentEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookContentReferenceEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookCreateEvent" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "WebhookDeleteEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebhookDeployKeyEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookDeploymentEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookDeploymentStatusEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookDiscussion" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookDiscussionComment" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookDownloadEvent" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "WebhookFollowEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebhookForkEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookGistEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookGitHubAppAuthorizationEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookGollumEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookInstallationEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookInstallationRepositoriesEvent" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "WebhookIssueCommentEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookIssuesEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookLabelEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookMarketplacePurchaseEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookMemberEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookMembershipEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookMetaEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookMilestoneEvent" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "WebhookOrgBlockEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebhookOrganizationEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookPackage" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookPageBuildEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookPingEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookProjectCardEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookProjectColumnEvent" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "WebhookProjectEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebhookPublicEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookPullRequestEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookPullRequestReviewCommentEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookPullRequestReviewEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookPushEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookRegistryPackageEvent" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "WebhookReleaseEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "WebhookRepositoryDispatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookRepositoryEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookRepositoryImportEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookRepositoryVulnerabilityAlertEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookSecretScanningAlert" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookSecurityAdvisoryEvent" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "WebhookSponsorship" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookStarEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookStatusEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookTeamAddEvent" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "WebhookTeamEvent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookWatchEvent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WebhookWorkflowDispatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WebhookWorkflowRun" 'PrefixI 'False) (U1 :: Type -> Type)))))))

data RepoWebhookResponse Source #

Instances

Instances details
Eq RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Data RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

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

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

toConstr :: RepoWebhookResponse -> Constr #

dataTypeOf :: RepoWebhookResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Show RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Generic RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Associated Types

type Rep RepoWebhookResponse :: Type -> Type #

FromJSON RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Binary RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

NFData RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

rnf :: RepoWebhookResponse -> () #

type Rep RepoWebhookResponse Source # 
Instance details

Defined in GitHub.Data.Webhooks

type Rep RepoWebhookResponse = D1 ('MetaData "RepoWebhookResponse" "GitHub.Data.Webhooks" "github-0.27-E2VX4APYqInCeK2QmfbNoQ" 'False) (C1 ('MetaCons "RepoWebhookResponse" 'PrefixI 'True) (S1 ('MetaSel ('Just "repoWebhookResponseCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "repoWebhookResponseStatus") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "repoWebhookResponseMessage") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Text)))))

data PingEvent Source #

Instances

Instances details
Eq PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Data PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

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

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

toConstr :: PingEvent -> Constr #

dataTypeOf :: PingEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Show PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Generic PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Associated Types

type Rep PingEvent :: Type -> Type #

FromJSON PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Binary PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

NFData PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

rnf :: PingEvent -> () #

type Rep PingEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks

type Rep PingEvent = D1 ('MetaData "PingEvent" "GitHub.Data.Webhooks" "github-0.27-E2VX4APYqInCeK2QmfbNoQ" 'False) (C1 ('MetaCons "PingEvent" 'PrefixI 'True) (S1 ('MetaSel ('Just "pingEventZen") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "pingEventHook") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RepoWebhook) :*: S1 ('MetaSel ('Just "pingEventHookId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Id RepoWebhook)))))

data NewRepoWebhook Source #

Instances

Instances details
Eq NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Data NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

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

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

toConstr :: NewRepoWebhook -> Constr #

dataTypeOf :: NewRepoWebhook -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Show NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Generic NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Associated Types

type Rep NewRepoWebhook :: Type -> Type #

ToJSON NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Binary NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

NFData NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

rnf :: NewRepoWebhook -> () #

type Rep NewRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

type Rep NewRepoWebhook = D1 ('MetaData "NewRepoWebhook" "GitHub.Data.Webhooks" "github-0.27-E2VX4APYqInCeK2QmfbNoQ" 'False) (C1 ('MetaCons "NewRepoWebhook" 'PrefixI 'True) ((S1 ('MetaSel ('Just "newRepoWebhookName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "newRepoWebhookConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Text Text))) :*: (S1 ('MetaSel ('Just "newRepoWebhookEvents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Vector RepoWebhookEvent))) :*: S1 ('MetaSel ('Just "newRepoWebhookActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool)))))

data EditRepoWebhook Source #

Instances

Instances details
Eq EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Data EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

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

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

toConstr :: EditRepoWebhook -> Constr #

dataTypeOf :: EditRepoWebhook -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Show EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Generic EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Associated Types

type Rep EditRepoWebhook :: Type -> Type #

ToJSON EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Binary EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

NFData EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

Methods

rnf :: EditRepoWebhook -> () #

type Rep EditRepoWebhook Source # 
Instance details

Defined in GitHub.Data.Webhooks

type Rep EditRepoWebhook = D1 ('MetaData "EditRepoWebhook" "GitHub.Data.Webhooks" "github-0.27-E2VX4APYqInCeK2QmfbNoQ" 'False) (C1 ('MetaCons "EditRepoWebhook" 'PrefixI 'True) ((S1 ('MetaSel ('Just "editRepoWebhookConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Map Text Text))) :*: S1 ('MetaSel ('Just "editRepoWebhookEvents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Vector RepoWebhookEvent)))) :*: (S1 ('MetaSel ('Just "editRepoWebhookAddEvents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Vector RepoWebhookEvent))) :*: (S1 ('MetaSel ('Just "editRepoWebhookRemoveEvents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe (Vector RepoWebhookEvent))) :*: S1 ('MetaSel ('Just "editRepoWebhookActive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Bool))))))