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

Copyright(c) ONROCK 2018
LicenseMIT
MaintainerKyle Van Berendonck <[email protected]>
Safe HaskellTrustworthy
LanguageHaskell2010

GitHub.Data.Webhooks.Events

Description

This module contains types that represent GitHub webhook's events.

Synopsis

Documentation

class EventHasSender eventKind where Source #

Represents an event that contains its sender information.

Methods

senderOfEvent :: eventKind -> HookUser Source #

Provides the sender context of a Webhook event.

Instances
EventHasSender WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

class EventHasRepo eventKind where Source #

Represents an event that contains its repository information.

Methods

repoForEvent :: eventKind -> HookRepository Source #

Provides the repository context of a Webhook event.

Instances
EventHasRepo WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

data CheckSuiteEventAction Source #

Represents the "action" field in the CheckSuiteEvent payload.

Constructors

CheckSuiteEventActionCompleted

Decodes from "completed"

CheckSuiteEventActionRequested

Decodes from "requested"

CheckSuiteEventActionRerequested

Decodes from "rerequested"

CheckSuiteEventActionOther !Text

The result of decoding an unknown check suite event action type

Instances
Eq CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CheckSuiteEventAction -> Constr #

dataTypeOf :: CheckSuiteEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CheckSuiteEventAction :: Type -> Type #

FromJSON CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: CheckSuiteEventAction -> () #

type Rep CheckSuiteEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CheckSuiteEventAction = D1 (MetaData "CheckSuiteEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "CheckSuiteEventActionCompleted" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CheckSuiteEventActionRequested" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CheckSuiteEventActionRerequested" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CheckSuiteEventActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data CheckSuiteEvent Source #

Triggered when a check suite is completed, requested, or rerequested. See https://developer.github.com/v3/activity/events/types/#checksuiteevent.

Instances
Eq CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CheckSuiteEvent -> Constr #

dataTypeOf :: CheckSuiteEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CheckSuiteEvent :: Type -> Type #

FromJSON CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: CheckSuiteEvent -> () #

EventHasRepo CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CheckSuiteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CheckSuiteEvent = D1 (MetaData "CheckSuiteEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "CheckSuiteEvent" PrefixI True) ((S1 (MetaSel (Just "evCheckSuiteAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CheckSuiteEventAction) :*: (S1 (MetaSel (Just "evCheckSuiteCheckSuite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookCheckSuite) :*: S1 (MetaSel (Just "evCheckSuiteRepository") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository))) :*: (S1 (MetaSel (Just "evCheckSuiteOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookOrganization)) :*: (S1 (MetaSel (Just "evCheckSuiteSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser) :*: S1 (MetaSel (Just "evCheckSuiteInstallation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookChecksInstallation))))))

data CheckRunEventAction Source #

Represents the "action" field in the CheckRunEvent payload.

Constructors

CheckRunEventActionCreated

Decodes from "created"

CheckRunEventActionCompleted

Decodes from "completed"

CheckRunEventActionRerequested

Decodes from "rerequested"

CheckRunEventActionRequestedAction

Decodes from "requested_action"

CheckRunEventActionOther !Text

The result of decoding an unknown check run event action type

Instances
Eq CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CheckRunEventAction -> Constr #

dataTypeOf :: CheckRunEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CheckRunEventAction :: Type -> Type #

FromJSON CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: CheckRunEventAction -> () #

type Rep CheckRunEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CheckRunEventAction = D1 (MetaData "CheckRunEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "CheckRunEventActionCreated" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CheckRunEventActionCompleted" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CheckRunEventActionRerequested" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CheckRunEventActionRequestedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CheckRunEventActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data CheckRunEvent Source #

Triggered when a check run is created, rerequested, completed, or has a requested_action. See https://developer.github.com/v3/activity/events/types/#checkrunevent.

Instances
Eq CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CheckRunEvent -> Constr #

dataTypeOf :: CheckRunEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CheckRunEvent :: Type -> Type #

FromJSON CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: CheckRunEvent -> () #

EventHasRepo CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CheckRunEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

data CommitCommentEvent Source #

Triggered when a commit comment is created. See https://developer.github.com/v3/activity/events/types/#commitcommentevent.

Instances
Eq CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CommitCommentEvent -> Constr #

dataTypeOf :: CommitCommentEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CommitCommentEvent :: Type -> Type #

FromJSON CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: CommitCommentEvent -> () #

EventHasRepo CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CommitCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CommitCommentEvent = D1 (MetaData "CommitCommentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "CommitCommentEvent" PrefixI True) ((S1 (MetaSel (Just "evCommitCommentAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CommitCommentEventAction) :*: S1 (MetaSel (Just "evCommitCommentPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookCommitComment)) :*: (S1 (MetaSel (Just "evCommitCommentRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evCommitCommentSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data CommitCommentEventAction Source #

Represents the "action" field in the CommitCommentEvent payload.

Constructors

CommitCommentActionCreated

Decodes from "created"

CommitCommentActionOther !Text

The result of decoding an unknown commit comment event action type

Instances
Eq CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CommitCommentEventAction -> Constr #

dataTypeOf :: CommitCommentEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CommitCommentEventAction :: Type -> Type #

FromJSON CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CommitCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CommitCommentEventAction = D1 (MetaData "CommitCommentEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "CommitCommentActionCreated" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CommitCommentActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data CreateEvent Source #

Represents a created repository, branch, or tag. Note: webhooks will not receive this event for created repositories. Additionally, webhooks will not receive this event for tags if more than three tags are pushed at once. See https://developer.github.com/v3/activity/events/types/#createevent.

Instances
Eq CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: CreateEvent -> Constr #

dataTypeOf :: CreateEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep CreateEvent :: Type -> Type #

FromJSON CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: CreateEvent -> () #

EventHasRepo CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CreateEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep CreateEvent = D1 (MetaData "CreateEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "CreateEvent" PrefixI True) ((S1 (MetaSel (Just "evCreateRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "evCreateRefType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "evCreateMasterBranch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :*: ((S1 (MetaSel (Just "evCreateDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "evCreatePusherType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OwnerType)) :*: (S1 (MetaSel (Just "evCreateRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evCreateSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data DeleteEvent Source #

Represents a deleted branch or tag. Note: webhooks will not receive this event for tags if more than three tags are deleted at once. See https://developer.github.com/v3/activity/events/types/#deleteevent.

Instances
Eq DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: DeleteEvent -> Constr #

dataTypeOf :: DeleteEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep DeleteEvent :: Type -> Type #

FromJSON DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: DeleteEvent -> () #

EventHasRepo DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep DeleteEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep DeleteEvent = D1 (MetaData "DeleteEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "DeleteEvent" PrefixI True) ((S1 (MetaSel (Just "evDeleteRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "evDeleteRefType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :*: (S1 (MetaSel (Just "evDeletePusherType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OwnerType) :*: (S1 (MetaSel (Just "evDeleteRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evDeleteSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data DeploymentEvent Source #

Represents a deployment. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#deploymentevent.

Instances
Eq DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: DeploymentEvent -> Constr #

dataTypeOf :: DeploymentEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep DeploymentEvent :: Type -> Type #

FromJSON DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: DeploymentEvent -> () #

EventHasRepo DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep DeploymentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep DeploymentEvent = D1 (MetaData "DeploymentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "DeploymentEvent" PrefixI True) (S1 (MetaSel (Just "evDeploymentInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookDeployment) :*: (S1 (MetaSel (Just "evDeploymentRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evDeploymentSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data DeploymentStatusEvent Source #

Represents a deployment status. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#deploymentstatusevent.

Instances
Eq DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: DeploymentStatusEvent -> Constr #

dataTypeOf :: DeploymentStatusEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep DeploymentStatusEvent :: Type -> Type #

FromJSON DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: DeploymentStatusEvent -> () #

EventHasRepo DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep DeploymentStatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep DeploymentStatusEvent = D1 (MetaData "DeploymentStatusEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "DeploymentStatusEvent" PrefixI True) ((S1 (MetaSel (Just "evDeplStatusInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookDeploymentStatus) :*: S1 (MetaSel (Just "evDeplStatusDeployment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookDeployment)) :*: (S1 (MetaSel (Just "evDeplStatusRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evDeplStatusSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data DownloadEvent Source #

Triggered when a new download is created. Events of this kind are no longer delivered. See https://developer.github.com/v3/activity/events/types/#downloadevent.

Constructors

DownloadEvent 

data FollowEvent Source #

Triggered when a user follows another user. Events of this kind are no longer delivered. See https://developer.github.com/v3/activity/events/types/#downloadevent.

Constructors

FollowEvent 

data ForkEvent Source #

Triggered when a user forks a repository. See https://developer.github.com/v3/activity/events/types/#forkevent.

Instances
Eq ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ForkEvent -> Constr #

dataTypeOf :: ForkEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ForkEvent :: Type -> Type #

FromJSON ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ForkEvent -> () #

EventHasRepo ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ForkEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ForkEvent = D1 (MetaData "ForkEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "ForkEvent" PrefixI True) (S1 (MetaSel (Just "evForkDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evForkSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evForkSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data ForkApplyEvent Source #

Triggered when a patch is applied in the Fork Queue. Events of this kind are no longer delivered. See https://developer.github.com/v3/activity/events/types/#forkapplyevent.

Constructors

ForkApplyEvent 

data GistEvent Source #

Triggered when a Gist is created or updated. Events of this kind are no longer delivered. See https://developer.github.com/v3/activity/events/types/#gistevent.

Constructors

GistEvent 

data GollumEvent Source #

Triggered when a Wiki page is created or updated. See https://developer.github.com/v3/activity/events/types/#gollumevent.

Instances
Eq GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: GollumEvent -> Constr #

dataTypeOf :: GollumEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep GollumEvent :: Type -> Type #

FromJSON GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: GollumEvent -> () #

EventHasRepo GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep GollumEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep GollumEvent = D1 (MetaData "GollumEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "GollumEvent" PrefixI True) (S1 (MetaSel (Just "evGollumPages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector HookWikiPage)) :*: (S1 (MetaSel (Just "evGollumRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evGollumSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data InstallationEvent Source #

Triggered when a GitHub App has been installed or uninstalled. See https://developer.github.com/v3/activity/events/types/#installationevent.

Instances
Eq InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: InstallationEvent -> Constr #

dataTypeOf :: InstallationEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep InstallationEvent :: Type -> Type #

FromJSON InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: InstallationEvent -> () #

EventHasSender InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationEvent = D1 (MetaData "InstallationEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "InstallationEvent" PrefixI True) ((S1 (MetaSel (Just "evInstallationAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 InstallationEventAction) :*: S1 (MetaSel (Just "evInstallationInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookInstallation)) :*: (S1 (MetaSel (Just "evInstallationRepos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector HookRepositorySimple)) :*: S1 (MetaSel (Just "evInstallationSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data InstallationEventAction Source #

Constructors

InstallationCreatedAction

Decodes from "created"

InstallationDeletedAction

Decodes from "deleted"

InstallationActionOther !Text

The result of decoding an unknown installation event action type

Instances
Eq InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: InstallationEventAction -> Constr #

dataTypeOf :: InstallationEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep InstallationEventAction :: Type -> Type #

FromJSON InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: InstallationEventAction -> () #

type Rep InstallationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationEventAction = D1 (MetaData "InstallationEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "InstallationCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "InstallationDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InstallationActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data InstallationRepositoriesEvent Source #

Triggered when a repository is added or removed from an installation. See https://developer.github.com/v3/activity/events/types/#installationrepositoriesevent.

Instances
Eq InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: InstallationRepositoriesEvent -> Constr #

dataTypeOf :: InstallationRepositoriesEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep InstallationRepositoriesEvent :: Type -> Type #

FromJSON InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationRepositoriesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationRepositoriesEvent = D1 (MetaData "InstallationRepositoriesEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "InstallationRepositoriesEvent" PrefixI True) ((S1 (MetaSel (Just "evInstallationRepoAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 InstallationRepoEventAction) :*: (S1 (MetaSel (Just "evInstallationRepoInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookInstallation) :*: S1 (MetaSel (Just "evInstallationRepoSel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) :*: (S1 (MetaSel (Just "evInstallationReposAdd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector HookRepositorySimple)) :*: (S1 (MetaSel (Just "evInstallationReposRemove") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Vector HookRepositorySimple)) :*: S1 (MetaSel (Just "evInstallationReposSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data InstallationRepoEventAction Source #

Constructors

InstallationRepoCreatedAction

Decodes from "created"

InstallationRepoRemovedAction

Decodes from "removed"

InstallationRepoActionOther !Text

The result of decoding an unknown installation repo event action type

Instances
Eq InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: InstallationRepoEventAction -> Constr #

dataTypeOf :: InstallationRepoEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep InstallationRepoEventAction :: Type -> Type #

FromJSON InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationRepoEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep InstallationRepoEventAction = D1 (MetaData "InstallationRepoEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "InstallationRepoCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "InstallationRepoRemovedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "InstallationRepoActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data IssueCommentEvent Source #

Triggered when an issue comment is created, edited, or deleted. See https://developer.github.com/v3/activity/events/types/#issuecommentevent.

Instances
Eq IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: IssueCommentEvent -> Constr #

dataTypeOf :: IssueCommentEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep IssueCommentEvent :: Type -> Type #

FromJSON IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: IssueCommentEvent -> () #

EventHasRepo IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep IssueCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep IssueCommentEvent = D1 (MetaData "IssueCommentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "IssueCommentEvent" PrefixI True) ((S1 (MetaSel (Just "evIssueCommentAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IssueCommentEventAction) :*: S1 (MetaSel (Just "evIssueCommentIssue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookIssue)) :*: (S1 (MetaSel (Just "evIssueCommentPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookIssueComment) :*: (S1 (MetaSel (Just "evIssueCommentRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evIssueCommentSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data IssueCommentEventAction Source #

Constructors

IssueCommentCreatedAction

Decodes from "created"

IssueCommentEditedAction

Decodes from "edited"

IssueCommentDeletedAction

Decodes from "deleted"

IssueCommentActionOther !Text

The result of decoding an unknown issue comment event action type

Instances
Eq IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: IssueCommentEventAction -> Constr #

dataTypeOf :: IssueCommentEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep IssueCommentEventAction :: Type -> Type #

FromJSON IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: IssueCommentEventAction -> () #

type Rep IssueCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep IssueCommentEventAction = D1 (MetaData "IssueCommentEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "IssueCommentCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IssueCommentEditedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IssueCommentDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IssueCommentActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data IssuesEvent Source #

Triggered when an issue is assigned, unassigned, labeled, unlabeled, opened, edited, milestoned, demilestoned, closed, or reopened. See https://developer.github.com/v3/activity/events/types/#issuesevent.

Instances
Eq IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: IssuesEvent -> Constr #

dataTypeOf :: IssuesEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep IssuesEvent :: Type -> Type #

FromJSON IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: IssuesEvent -> () #

EventHasRepo IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep IssuesEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep IssuesEvent = D1 (MetaData "IssuesEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "IssuesEvent" PrefixI True) ((S1 (MetaSel (Just "evIssuesEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 IssuesEventAction) :*: S1 (MetaSel (Just "evIssuesEventIssue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookIssue)) :*: (S1 (MetaSel (Just "evIssuesEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evIssuesEventSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data IssuesEventAction Source #

Constructors

IssuesAssignedAction

Decodes from "assigned"

IssuesUnassignedAction

Decodes from "unassigned"

IssuesLabeledAction

Decodes from "labeled"

IssuesUnlabeledAction

Decodes from "unlabeled"

IssuesOpenedAction

Decodes from "opened"

IssuesEditedAction

Decodes from "edited"

IssuesMilestonedAction

Decodes from "milestoned"

IssuesDemilestonedAction

Decodes from "demilestoned"

IssuesClosedAction

Decodes from "closed"

IssuesReopenedAction

Decodes from "reopened"

IssuesActionOther !Text

The result of decoding an unknown issue comment event action type

Instances
Eq IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: IssuesEventAction -> Constr #

dataTypeOf :: IssuesEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep IssuesEventAction :: Type -> Type #

FromJSON IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: IssuesEventAction -> () #

type Rep IssuesEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep IssuesEventAction = D1 (MetaData "IssuesEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (((C1 (MetaCons "IssuesAssignedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IssuesUnassignedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "IssuesLabeledAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IssuesUnlabeledAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IssuesOpenedAction" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "IssuesEditedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IssuesMilestonedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IssuesDemilestonedAction" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "IssuesClosedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "IssuesReopenedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "IssuesActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

data LabelEvent Source #

Triggered when a repository's label is created, edited, or deleted. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#labelevent.

Instances
Eq LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: LabelEvent -> Constr #

dataTypeOf :: LabelEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep LabelEvent :: Type -> Type #

FromJSON LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: LabelEvent -> () #

EventHasRepo LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep LabelEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep LabelEvent = D1 (MetaData "LabelEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "LabelEvent" PrefixI True) ((S1 (MetaSel (Just "evLabelEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LabelEventAction) :*: S1 (MetaSel (Just "evLabelEventPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepositoryLabel)) :*: (S1 (MetaSel (Just "evLabelEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evLabelEventOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookOrganization)) :*: S1 (MetaSel (Just "evLabelEventSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data LabelEventAction Source #

Constructors

LabelCreatedAction

Decodes from "created"

LabelEditedAction

Decodes from "edited"

LabelDeletedAction

Decodes from "deleted"

LabelActionOther !Text

The result of decoding an unknown label event action type

Instances
Eq LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: LabelEventAction -> Constr #

dataTypeOf :: LabelEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep LabelEventAction :: Type -> Type #

FromJSON LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: LabelEventAction -> () #

type Rep LabelEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep LabelEventAction = D1 (MetaData "LabelEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "LabelCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LabelEditedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LabelDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LabelActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data MemberEvent Source #

Triggered when a user is added or removed as a collaborator to a repository, or has their permissions changed. See https://developer.github.com/v3/activity/events/types/#memberevent.

Instances
Eq MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: MemberEvent -> Constr #

dataTypeOf :: MemberEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep MemberEvent :: Type -> Type #

FromJSON MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: MemberEvent -> () #

EventHasRepo MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MemberEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MemberEvent = D1 (MetaData "MemberEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "MemberEvent" PrefixI True) ((S1 (MetaSel (Just "evMemberAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MemberEventAction) :*: S1 (MetaSel (Just "evMemberUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)) :*: (S1 (MetaSel (Just "evMemberRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evMemberSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data MemberEventAction Source #

Constructors

MemberAddedAction

Decodes from "added"

MemberEditedAction

Decodes from "edited"

MemberDeletedAction

Decodes from "deleted"

MemberActionOther !Text

The result of decoding an unknown label event action type

Instances
Eq MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: MemberEventAction -> Constr #

dataTypeOf :: MemberEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep MemberEventAction :: Type -> Type #

FromJSON MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: MemberEventAction -> () #

type Rep MemberEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MemberEventAction = D1 (MetaData "MemberEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "MemberAddedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MemberEditedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MemberDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MemberActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data MembershipEvent Source #

Triggered when a user is added or removed from a team. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#membershipevent.

Instances
Eq MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: MembershipEvent -> Constr #

dataTypeOf :: MembershipEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep MembershipEvent :: Type -> Type #

FromJSON MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: MembershipEvent -> () #

EventHasSender MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MembershipEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MembershipEvent = D1 (MetaData "MembershipEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "MembershipEvent" PrefixI True) ((S1 (MetaSel (Just "evMembershipAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MembershipEventAction) :*: (S1 (MetaSel (Just "evMembershipScope") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "evMembershipUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))) :*: (S1 (MetaSel (Just "evMembershipTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookTeam) :*: (S1 (MetaSel (Just "evMembershipOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evMembershipSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data MembershipEventAction Source #

Constructors

MembershipAddedAction

Decodes from "added"

MembershipRemovedAction

Decodes from "removed"

MembershipActionOther !Text

The result of decoding an unknown label event action type

Instances
Eq MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: MembershipEventAction -> Constr #

dataTypeOf :: MembershipEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep MembershipEventAction :: Type -> Type #

FromJSON MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: MembershipEventAction -> () #

type Rep MembershipEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MembershipEventAction = D1 (MetaData "MembershipEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "MembershipAddedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MembershipRemovedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MembershipActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data MilestoneEvent Source #

Triggered when a milestone is created, closed, opened, edited, or deleted. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#milestoneevent.

Instances
Eq MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: MilestoneEvent -> Constr #

dataTypeOf :: MilestoneEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep MilestoneEvent :: Type -> Type #

FromJSON MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: MilestoneEvent -> () #

EventHasRepo MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MilestoneEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MilestoneEvent = D1 (MetaData "MilestoneEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "MilestoneEvent" PrefixI True) ((S1 (MetaSel (Just "evMilestoneAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MilestoneEventAction) :*: S1 (MetaSel (Just "evMilestoenPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookMilestone)) :*: (S1 (MetaSel (Just "evMilestoneRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evMilestoneOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evMilestoneSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data MilestoneEventAction Source #

Constructors

MilestoneCreatedAction

Decodes from "created"

MilestoneClosedAction

Decodes from "closed"

MilestoneOpenedAction

Decodes from "opened"

MilestoneEditedAction

Decodes from "edited"

MilestoneDeletedAction

Decodes from "deleted"

MilestoneActionOther !Text

The result of decoding an unknown label event action type

Instances
Eq MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: MilestoneEventAction -> Constr #

dataTypeOf :: MilestoneEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep MilestoneEventAction :: Type -> Type #

FromJSON MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: MilestoneEventAction -> () #

type Rep MilestoneEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep MilestoneEventAction = D1 (MetaData "MilestoneEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "MilestoneCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MilestoneClosedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MilestoneOpenedAction" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "MilestoneEditedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MilestoneDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MilestoneActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data OrganizationEvent Source #

Triggered when a user is added, removed, or invited to an Organization. Events of this type are not visible in timelines. These events are only used to trigger organization hooks. See https://developer.github.com/v3/activity/events/types/#organizationevent.

Instances
Eq OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: OrganizationEvent -> Constr #

dataTypeOf :: OrganizationEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep OrganizationEvent :: Type -> Type #

FromJSON OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: OrganizationEvent -> () #

EventHasSender OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep OrganizationEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep OrganizationEvent = D1 (MetaData "OrganizationEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "OrganizationEvent" PrefixI True) ((S1 (MetaSel (Just "evOrganizationAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OrganizationEventAction) :*: S1 (MetaSel (Just "evOrganizationInvitation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganizationInvitation)) :*: (S1 (MetaSel (Just "evOrganizationMembership") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganizationMembership) :*: (S1 (MetaSel (Just "evOrganizationOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evOrganizationSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data OrganizationEventAction Source #

Constructors

OrgMemberAddedAction

Decodes from "member_added"

OrgMemberRemovedAction

Decodes from "member_removed"

OrgMemberInvitedAction

Decodes from "member_invited"

OrgActionOther !Text

The result of decoding an unknown label event action type

Instances
Eq OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: OrganizationEventAction -> Constr #

dataTypeOf :: OrganizationEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep OrganizationEventAction :: Type -> Type #

FromJSON OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: OrganizationEventAction -> () #

type Rep OrganizationEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep OrganizationEventAction = D1 (MetaData "OrganizationEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "OrgMemberAddedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OrgMemberRemovedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "OrgMemberInvitedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OrgActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data OrgBlockEvent Source #

Triggered when an organization blocks or unblocks a user. See https://developer.github.com/v3/activity/events/types/#orgblockevent.

Instances
Eq OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: OrgBlockEvent -> Constr #

dataTypeOf :: OrgBlockEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep OrgBlockEvent :: Type -> Type #

FromJSON OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: OrgBlockEvent -> () #

EventHasSender OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep OrgBlockEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep OrgBlockEvent = D1 (MetaData "OrgBlockEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "OrgBlockEvent" PrefixI True) ((S1 (MetaSel (Just "evOrgBlockAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 OrgBlockEventAction) :*: S1 (MetaSel (Just "evOrgBlockUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)) :*: (S1 (MetaSel (Just "evOrgBlockOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evOrgBlockSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data OrgBlockEventAction Source #

Constructors

OrgBlockBlockedAction

Decodes from "blocked"

OrgBlockUnblockedAction

Decodes from "unblocked"

OrgBlockActionOther !Text

The result of decoding an unknown org block event action type

Instances
Eq OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: OrgBlockEventAction -> Constr #

dataTypeOf :: OrgBlockEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep OrgBlockEventAction :: Type -> Type #

FromJSON OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: OrgBlockEventAction -> () #

type Rep OrgBlockEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep OrgBlockEventAction = D1 (MetaData "OrgBlockEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "OrgBlockBlockedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "OrgBlockUnblockedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "OrgBlockActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data PageBuildEvent Source #

Represents an attempted build of a GitHub Pages site, whether successful or not. Triggered on push to a GitHub Pages enabled branch (gh-pages for project pages, master for user and organization pages). Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#pagebuildevent.

Instances
Eq PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PageBuildEvent -> Constr #

dataTypeOf :: PageBuildEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PageBuildEvent :: Type -> Type #

FromJSON PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: PageBuildEvent -> () #

EventHasRepo PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PageBuildEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PageBuildEvent = D1 (MetaData "PageBuildEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "PageBuildEvent" PrefixI True) ((S1 (MetaSel (Just "evPageBuildId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "evPageBuildResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookPageBuildResult)) :*: (S1 (MetaSel (Just "evPageBuildRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evPageBuildSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data ProjectCardEvent Source #

Triggered when a project card is created, updated, moved, converted to an issue, or deleted. See https://developer.github.com/v3/activity/events/types/#projectcardevent.

Instances
Eq ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ProjectCardEvent -> Constr #

dataTypeOf :: ProjectCardEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ProjectCardEvent :: Type -> Type #

FromJSON ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ProjectCardEvent -> () #

EventHasRepo ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectCardEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectCardEvent = D1 (MetaData "ProjectCardEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "ProjectCardEvent" PrefixI True) ((S1 (MetaSel (Just "evProjectCardAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProjectCardEventAction) :*: S1 (MetaSel (Just "evProjectCardPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookProjectCard)) :*: (S1 (MetaSel (Just "evProjectCardRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evProjectCardOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evProjectCardSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data ProjectCardEventAction Source #

Constructors

ProjectCardCreatedAction

Decodes from "created"

ProjectCardEditedAction

Decodes from "edited"

ProjectCardConvertedAction

Decodes from "converted"

ProjectCardMovedAction

Decodes from "moved"

ProjectCardDeletedAction

Decodes from "deleted"

ProjectCardActionOther !Text

The result of decoding an unknown project card event action type

Instances
Eq ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ProjectCardEventAction -> Constr #

dataTypeOf :: ProjectCardEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ProjectCardEventAction :: Type -> Type #

FromJSON ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ProjectCardEventAction -> () #

type Rep ProjectCardEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectCardEventAction = D1 (MetaData "ProjectCardEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "ProjectCardCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProjectCardEditedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProjectCardConvertedAction" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "ProjectCardMovedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProjectCardDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProjectCardActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data ProjectColumnEvent Source #

Triggered when a project column is created, updated, moved, or deleted. See https://developer.github.com/v3/activity/events/types/#projectcolumnevent.

Instances
Eq ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ProjectColumnEvent -> Constr #

dataTypeOf :: ProjectColumnEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ProjectColumnEvent :: Type -> Type #

FromJSON ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ProjectColumnEvent -> () #

EventHasRepo ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectColumnEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectColumnEvent = D1 (MetaData "ProjectColumnEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "ProjectColumnEvent" PrefixI True) ((S1 (MetaSel (Just "evProjectColumnAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProjectColumnEventAction) :*: S1 (MetaSel (Just "evProjectColumnPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookProjectColumn)) :*: (S1 (MetaSel (Just "evProjectColumnRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evProjectColumnOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evProjectColumnSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data ProjectColumnEventAction Source #

Constructors

ProjectColumnCreatedAction

Decodes from "created"

ProjectColumnEditedAction

Decodes from "edited"

ProjectColumnMovedAction

Decodes from "moved"

ProjectColumnDeletedAction

Decodes from "deleted"

ProjectColumnActionOther !Text

The result of decoding an unknown project card event action type

Instances
Eq ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ProjectColumnEventAction -> Constr #

dataTypeOf :: ProjectColumnEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ProjectColumnEventAction :: Type -> Type #

FromJSON ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectColumnEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectColumnEventAction = D1 (MetaData "ProjectColumnEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "ProjectColumnCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProjectColumnEditedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ProjectColumnMovedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProjectColumnDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProjectColumnActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data ProjectEvent Source #

Triggered when a project is created, updated, closed, reopened, or deleted. See https://developer.github.com/v3/activity/events/types/#projectevent.

Instances
Eq ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ProjectEvent -> Constr #

dataTypeOf :: ProjectEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ProjectEvent :: Type -> Type #

FromJSON ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ProjectEvent -> () #

EventHasRepo ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectEvent = D1 (MetaData "ProjectEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "ProjectEvent" PrefixI True) ((S1 (MetaSel (Just "evProjectEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ProjectEventAction) :*: S1 (MetaSel (Just "evProjectPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookProject)) :*: (S1 (MetaSel (Just "evProjectRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evProjectOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evProjectSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data ProjectEventAction Source #

Constructors

ProjectCreatedAction

Decodes from "created"

ProjectEditedAction

Decodes from "edited"

ProjectClosedAction

Decodes from "closed"

ProjectReopenedAction

Decodes from "reopened"

ProjectDeletedAction

Decodes from "deleted"

ProjectActionOther !Text

The result of decoding an unknown project event action type

Instances
Eq ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ProjectEventAction -> Constr #

dataTypeOf :: ProjectEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ProjectEventAction :: Type -> Type #

FromJSON ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ProjectEventAction -> () #

type Rep ProjectEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ProjectEventAction = D1 (MetaData "ProjectEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "ProjectCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProjectEditedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProjectClosedAction" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "ProjectReopenedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ProjectDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ProjectActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data PublicEvent Source #

Triggered when a private repository is open sourced. Without a doubt: the best GitHub event. See https://developer.github.com/v3/activity/events/types/#publicevent.

Instances
Eq PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PublicEvent -> Constr #

dataTypeOf :: PublicEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PublicEvent :: Type -> Type #

FromJSON PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: PublicEvent -> () #

EventHasRepo PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PublicEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PublicEvent = D1 (MetaData "PublicEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "PublicEvent" PrefixI True) (S1 (MetaSel (Just "evPublicEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evPublicEventSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))

data PullRequestEvent Source #

Triggered when a pull request is assigned, unassigned, labeled, unlabeled, opened, edited, closed, reopened, or synchronized. Also triggered when a pull request review is requested, or when a review request is removed. See https://developer.github.com/v3/activity/events/types/#pullrequestevent.

Instances
Eq PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PullRequestEvent -> Constr #

dataTypeOf :: PullRequestEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PullRequestEvent :: Type -> Type #

FromJSON PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: PullRequestEvent -> () #

EventHasRepo PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestEvent = D1 (MetaData "PullRequestEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "PullRequestEvent" PrefixI True) ((S1 (MetaSel (Just "evPullReqAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PullRequestEventAction) :*: (S1 (MetaSel (Just "evPullReqNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "evPullReqPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookPullRequest))) :*: (S1 (MetaSel (Just "evPullReqRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: (S1 (MetaSel (Just "evPullReqSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser) :*: S1 (MetaSel (Just "evPullReqInstallationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Int))))))

data PullRequestEventAction Source #

Constructors

PullRequestAssignedAction

Decodes from "assigned"

PullRequestUnassignedAction

Decodes from "unassigned"

PullRequestReviewRequestedAction

Decodes from "review_requsted"

PullRequestReviewRequestRemovedAction

Decodes from "review_request_removed"

PullRequestLabeledAction

Decodes from "labeled"

PullRequestUnlabeledAction

Decodes from "unlabeled"

PullRequestOpenedAction

Decodes from "opened"

PullRequestEditedAction

Decodes from "edited"

PullRequestClosedAction

Decodes from "closed"

PullRequestReopenedAction

Decodes from "reopened"

PullRequestActionOther !Text

The result of decoding an unknown pull request event action type

Instances
Eq PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PullRequestEventAction -> Constr #

dataTypeOf :: PullRequestEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PullRequestEventAction :: Type -> Type #

FromJSON PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: PullRequestEventAction -> () #

type Rep PullRequestEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestEventAction = D1 (MetaData "PullRequestEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (((C1 (MetaCons "PullRequestAssignedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestUnassignedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PullRequestReviewRequestedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PullRequestReviewRequestRemovedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestLabeledAction" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "PullRequestUnlabeledAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PullRequestOpenedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestEditedAction" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "PullRequestClosedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PullRequestReopenedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

data PullRequestReviewEvent Source #

Triggered when a pull request review is submitted into a non-pending state, the body is edited, or the review is dismissed. See https://developer.github.com/v3/activity/events/types/#pullrequestreviewevent.

Instances
Eq PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PullRequestReviewEvent -> Constr #

dataTypeOf :: PullRequestReviewEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PullRequestReviewEvent :: Type -> Type #

FromJSON PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: PullRequestReviewEvent -> () #

EventHasRepo PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewEvent = D1 (MetaData "PullRequestReviewEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "PullRequestReviewEvent" PrefixI True) ((S1 (MetaSel (Just "evPullReqReviewAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PullRequestReviewEventAction) :*: S1 (MetaSel (Just "evPullReqReviewPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookPullRequestReview)) :*: (S1 (MetaSel (Just "evPullReqReviewTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookPullRequest) :*: (S1 (MetaSel (Just "evPullReqReviewRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evPullReqReviewSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data PullRequestReviewEventAction Source #

Constructors

PullRequestReviewSubmittedAction

Decodes from "submitted"

PullRequestReviewEditedAction

Decodes from "edited"

PullRequestReviewDismissedAction

Decodes from "dismissed"

PullRequestReviewActionOther !Text

The result of decoding an unknown pull request review event action type

Instances
Eq PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PullRequestReviewEventAction -> Constr #

dataTypeOf :: PullRequestReviewEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PullRequestReviewEventAction :: Type -> Type #

FromJSON PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewEventAction = D1 (MetaData "PullRequestReviewEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "PullRequestReviewSubmittedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestReviewEditedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PullRequestReviewDismissedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestReviewActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data PullRequestReviewCommentEvent Source #

Triggered when a comment on a pull request's unified diff is created, edited, or deleted (in the Files Changed tab). See https://developer.github.com/v3/activity/events/types/#pullrequestreviewcommentevent.

Instances
Eq PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PullRequestReviewCommentEvent -> Constr #

dataTypeOf :: PullRequestReviewCommentEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PullRequestReviewCommentEvent :: Type -> Type #

FromJSON PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasRepo PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewCommentEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewCommentEvent = D1 (MetaData "PullRequestReviewCommentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "PullRequestReviewCommentEvent" PrefixI True) ((S1 (MetaSel (Just "evPullReqRevComAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PullRequestReviewCommentEventAction) :*: S1 (MetaSel (Just "evPullReqRevComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookPullRequestReviewComment)) :*: (S1 (MetaSel (Just "evPullReqRevTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookPullRequest) :*: (S1 (MetaSel (Just "evPullReqRevRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evPullReqRevSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser)))))

data PullRequestReviewCommentEventAction Source #

Constructors

PullRequestReviewCommentCreatedAction

Decodes from "created"

PullRequestReviewCommentEditedAction

Decodes from "edited"

PullRequestReviewCommentDeletedAction

Decodes from "deleted"

PullRequestReviewCommentActionOther !Text

The result of decoding an unknown pull request review comment event action type

Instances
Eq PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PullRequestReviewCommentEventAction -> Constr #

dataTypeOf :: PullRequestReviewCommentEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

FromJSON PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewCommentEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PullRequestReviewCommentEventAction = D1 (MetaData "PullRequestReviewCommentEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "PullRequestReviewCommentCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestReviewCommentEditedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PullRequestReviewCommentDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PullRequestReviewCommentActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))

data PushEvent Source #

Triggered on a push to a repository branch. Branch pushes and repository tag pushes also trigger webhook push events. See https://developer.github.com/v3/activity/events/types/#pushevent.

Instances
Eq PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: PushEvent -> Constr #

dataTypeOf :: PushEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep PushEvent :: Type -> Type #

FromJSON PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: PushEvent -> () #

EventHasRepo PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PushEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep PushEvent = D1 (MetaData "PushEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "PushEvent" PrefixI True) (((S1 (MetaSel (Just "evPushRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "evPushHeadSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "evPushBeforeSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: (S1 (MetaSel (Just "evPushCreated") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: (S1 (MetaSel (Just "evPushDeleted") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "evPushForced") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))) :*: ((S1 (MetaSel (Just "evPushBaseRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "evPushCompareUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 URL) :*: S1 (MetaSel (Just "evPushCommits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Vector HookCommit))))) :*: ((S1 (MetaSel (Just "evPushHeadCommit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookCommit)) :*: S1 (MetaSel (Just "evPushRepository") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository)) :*: (S1 (MetaSel (Just "evPushOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookOrganization)) :*: S1 (MetaSel (Just "evPushSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))))

data ReleaseEvent Source #

Instances
Eq ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ReleaseEvent -> Constr #

dataTypeOf :: ReleaseEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ReleaseEvent :: Type -> Type #

FromJSON ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ReleaseEvent -> () #

EventHasRepo ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ReleaseEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ReleaseEvent = D1 (MetaData "ReleaseEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "ReleaseEvent" PrefixI True) ((S1 (MetaSel (Just "evReleaseEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ReleaseEventAction) :*: S1 (MetaSel (Just "evReleaseEventPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRelease)) :*: (S1 (MetaSel (Just "evReleaseEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evReleaseEventSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data ReleaseEventAction Source #

Constructors

ReleasePublishedAction

Decodes from "published"

ReleaseActionOther !Text

The result of decoding an unknown release event action type

Instances
Eq ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: ReleaseEventAction -> Constr #

dataTypeOf :: ReleaseEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep ReleaseEventAction :: Type -> Type #

FromJSON ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: ReleaseEventAction -> () #

type Rep ReleaseEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep ReleaseEventAction = D1 (MetaData "ReleaseEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "ReleasePublishedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ReleaseActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data RepositoryEvent Source #

Triggered when a repository is created, archived, unarchived, made public, or made private. Organization hooks are also triggered when a repository is deleted. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#repositoryevent.

Instances
Eq RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: RepositoryEvent -> Constr #

dataTypeOf :: RepositoryEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep RepositoryEvent :: Type -> Type #

FromJSON RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: RepositoryEvent -> () #

EventHasRepo RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep RepositoryEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep RepositoryEvent = D1 (MetaData "RepositoryEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "RepositoryEvent" PrefixI True) ((S1 (MetaSel (Just "evRepositoryAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 RepositoryEventAction) :*: S1 (MetaSel (Just "evRepositoryTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository)) :*: (S1 (MetaSel (Just "evRepositoryOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookOrganization)) :*: S1 (MetaSel (Just "evRepositorySender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data RepositoryEventAction Source #

Constructors

RepositoryCreatedAction

Decodes from "created"

RepositoryDeletedAction

Decodes from "deleted"

RepositoryArchivedAction

Decodes from "archived"

RepositoryUnarchivedAction

Decodes from "unarchived"

RepositoryPublicizedAction

Decodes from "publicized"

RepositoryPrivatizedAction

Decodes from "privatized"

RepositoryActionOther !Text

The result of decoding an unknown repository event action type

Instances
Eq RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: RepositoryEventAction -> Constr #

dataTypeOf :: RepositoryEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep RepositoryEventAction :: Type -> Type #

FromJSON RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: RepositoryEventAction -> () #

type Rep RepositoryEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep RepositoryEventAction = D1 (MetaData "RepositoryEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "RepositoryCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RepositoryDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RepositoryArchivedAction" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "RepositoryUnarchivedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RepositoryPublicizedAction" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "RepositoryPrivatizedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RepositoryActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data StatusEvent Source #

Triggered when the status of a Git commit changes. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#statusevent.

Instances
Eq StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: StatusEvent -> Constr #

dataTypeOf :: StatusEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep StatusEvent :: Type -> Type #

FromJSON StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: StatusEvent -> () #

EventHasRepo StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep StatusEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

data StatusEventState Source #

Constructors

StatusPendingState

Decodes from "pending"

StatusSuccessState

Decodes from "success"

StatusFailureState

Decodes from "failure"

StatusErrorState

Decodes from "error"

StatusStateOther !Text

The result of decoding an unknown status event state

Instances
Eq StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: StatusEventState -> Constr #

dataTypeOf :: StatusEventState -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep StatusEventState :: Type -> Type #

FromJSON StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: StatusEventState -> () #

type Rep StatusEventState Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep StatusEventState = D1 (MetaData "StatusEventState" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "StatusPendingState" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StatusSuccessState" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "StatusFailureState" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "StatusErrorState" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "StatusStateOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data TeamEvent Source #

Triggered when an organization's team is created or deleted. Events of this type are not visible in timelines. These events are only used to trigger organization hooks. See https://developer.github.com/v3/activity/events/types/#teamevent.

Instances
Eq TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: TeamEvent -> Constr #

dataTypeOf :: TeamEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep TeamEvent :: Type -> Type #

FromJSON TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: TeamEvent -> () #

EventHasSender TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep TeamEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep TeamEvent = D1 (MetaData "TeamEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "TeamEvent" PrefixI True) ((S1 (MetaSel (Just "evTeamAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TeamEventAction) :*: S1 (MetaSel (Just "evTeamTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookTeam)) :*: (S1 (MetaSel (Just "evTeamOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evTeamSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data TeamEventAction Source #

Constructors

TeamCreatedAction

Decodes from "created"

TeamDeletedAction

Decodes from "deleted"

TeamEditedAction

Decodes from "edited"

TeamAddedToRepoAction

Decodes from "added_to_repository"

TeamRemovedFromRepoAction

Decodes from "removed_from_repository"

TeamActionOther !Text

The result of decoding an unknown team event action type

Instances
Eq TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: TeamEventAction -> Constr #

dataTypeOf :: TeamEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep TeamEventAction :: Type -> Type #

FromJSON TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: TeamEventAction -> () #

type Rep TeamEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep TeamEventAction = D1 (MetaData "TeamEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) ((C1 (MetaCons "TeamCreatedAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TeamDeletedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TeamEditedAction" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "TeamAddedToRepoAction" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TeamRemovedFromRepoAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TeamActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))))

data TeamAddEvent Source #

Triggered when a repository is added to a team. Events of this type are not visible in timelines. These events are only used to trigger hooks. See https://developer.github.com/v3/activity/events/types/#teamaddevent.

Constructors

TeamAddEvent 

Fields

Instances
Eq TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: TeamAddEvent -> Constr #

dataTypeOf :: TeamAddEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep TeamAddEvent :: Type -> Type #

FromJSON TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: TeamAddEvent -> () #

EventHasRepo TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep TeamAddEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep TeamAddEvent = D1 (MetaData "TeamAddEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "TeamAddEvent" PrefixI True) ((S1 (MetaSel (Just "evTeamAddTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe HookTeam)) :*: S1 (MetaSel (Just "evTeamAddRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository)) :*: (S1 (MetaSel (Just "evTeamAddOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookOrganization) :*: S1 (MetaSel (Just "evTeamAddSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data WatchEvent Source #

The WatchEvent is related to starring a repository, not watching. The event’s actor is the user who starred a repository, and the event’s repository is the repository that was starred. See https://developer.github.com/v3/activity/events/types/#watchevent.

Instances
Eq WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: WatchEvent -> Constr #

dataTypeOf :: WatchEvent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep WatchEvent :: Type -> Type #

FromJSON WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: WatchEvent -> () #

EventHasRepo WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

EventHasSender WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep WatchEvent Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep WatchEvent = D1 (MetaData "WatchEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "WatchEvent" PrefixI True) (S1 (MetaSel (Just "evWatchAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WatchEventAction) :*: (S1 (MetaSel (Just "evWatchRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookRepository) :*: S1 (MetaSel (Just "evWatchSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 HookUser))))

data WatchEventAction Source #

Constructors

WatchStartedAction

Decodes from "started"

WatchActionOther !Text

The result of decoding an unknown watch event action type

Instances
Eq WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Data WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

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

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

toConstr :: WatchEventAction -> Constr #

dataTypeOf :: WatchEventAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Show WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Generic WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Associated Types

type Rep WatchEventAction :: Type -> Type #

FromJSON WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

NFData WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

Methods

rnf :: WatchEventAction -> () #

type Rep WatchEventAction Source # 
Instance details

Defined in GitHub.Data.Webhooks.Events

type Rep WatchEventAction = D1 (MetaData "WatchEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.14.0-sgY79mCHyP1Ay0QYF4e1N" False) (C1 (MetaCons "WatchStartedAction" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WatchActionOther" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))