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

Safe HaskellTrustworthy
LanguageHaskell2010

GitHub.Data.Webhooks.Events

Synopsis

Documentation

class EventHasSender eventKind where Source #

Minimal complete definition

senderOfEvent

Methods

senderOfEvent :: eventKind -> HookUser Source #

Provides the sender context of a Webhook event.

Instances

EventHasSender WatchEvent Source # 
EventHasSender TeamAddEvent Source # 
EventHasSender TeamEvent Source # 
EventHasSender StatusEvent Source # 
EventHasSender RepositoryEvent Source # 
EventHasSender ReleaseEvent Source # 
EventHasSender PushEvent Source # 
EventHasSender PullRequestReviewCommentEvent Source # 
EventHasSender PullRequestReviewEvent Source # 
EventHasSender PullRequestEvent Source # 
EventHasSender PublicEvent Source # 
EventHasSender ProjectEvent Source # 
EventHasSender ProjectColumnEvent Source # 
EventHasSender ProjectCardEvent Source # 
EventHasSender PageBuildEvent Source # 
EventHasSender OrgBlockEvent Source # 
EventHasSender OrganizationEvent Source # 
EventHasSender MilestoneEvent Source # 
EventHasSender MembershipEvent Source # 
EventHasSender MemberEvent Source # 
EventHasSender LabelEvent Source # 
EventHasSender IssuesEvent Source # 
EventHasSender IssueCommentEvent Source # 
EventHasSender InstallationRepositoriesEvent Source # 
EventHasSender InstallationEvent Source # 
EventHasSender GollumEvent Source # 
EventHasSender ForkEvent Source # 
EventHasSender DeploymentStatusEvent Source # 
EventHasSender DeploymentEvent Source # 
EventHasSender DeleteEvent Source # 
EventHasSender CreateEvent Source # 
EventHasSender CommitCommentEvent Source # 

class EventHasRepo eventKind where Source #

Minimal complete definition

repoForEvent

Methods

repoForEvent :: eventKind -> HookRepository Source #

Provides the repository context of a Webhook event.

Instances

EventHasRepo WatchEvent Source # 
EventHasRepo TeamAddEvent Source # 
EventHasRepo StatusEvent Source # 
EventHasRepo RepositoryEvent Source # 
EventHasRepo ReleaseEvent Source # 
EventHasRepo PushEvent Source # 
EventHasRepo PullRequestReviewCommentEvent Source # 
EventHasRepo PullRequestReviewEvent Source # 
EventHasRepo PullRequestEvent Source # 
EventHasRepo PublicEvent Source # 
EventHasRepo ProjectEvent Source # 
EventHasRepo ProjectColumnEvent Source # 
EventHasRepo ProjectCardEvent Source # 
EventHasRepo PageBuildEvent Source # 
EventHasRepo MilestoneEvent Source # 
EventHasRepo MemberEvent Source # 
EventHasRepo LabelEvent Source # 
EventHasRepo IssuesEvent Source # 
EventHasRepo IssueCommentEvent Source # 
EventHasRepo GollumEvent Source # 
EventHasRepo ForkEvent Source # 
EventHasRepo DeploymentStatusEvent Source # 
EventHasRepo DeploymentEvent Source # 
EventHasRepo DeleteEvent Source # 
EventHasRepo CreateEvent Source # 
EventHasRepo CommitCommentEvent Source # 

data CommitCommentEvent Source #

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

Instances

Eq CommitCommentEvent Source # 
Data CommitCommentEvent Source # 

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 # 
Generic CommitCommentEvent Source # 
FromJSON CommitCommentEvent Source # 
NFData CommitCommentEvent Source # 

Methods

rnf :: CommitCommentEvent -> () #

EventHasRepo CommitCommentEvent Source # 
EventHasSender CommitCommentEvent Source # 
type Rep CommitCommentEvent Source # 
type Rep CommitCommentEvent = D1 * (MetaData "CommitCommentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "CommitCommentEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evCommitCommentAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CommitCommentEventAction)) (S1 * (MetaSel (Just Symbol "evCommitCommentPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookCommitComment))) ((:*:) * (S1 * (MetaSel (Just Symbol "evCommitCommentRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "evCommitCommentSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser)))))

data CommitCommentEventAction Source #

Constructors

CommitCommentActionCreated

Decodes from "created"

CommitCommentActionOther !Text

The result of decoding an unknown commit comment event action type

Instances

Eq CommitCommentEventAction Source # 
Data CommitCommentEventAction Source # 

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 # 
Show CommitCommentEventAction Source # 
Generic CommitCommentEventAction Source # 
FromJSON CommitCommentEventAction Source # 
NFData CommitCommentEventAction Source # 
type Rep CommitCommentEventAction Source # 
type Rep CommitCommentEventAction = D1 * (MetaData "CommitCommentEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "CommitCommentActionCreated" PrefixI False) (U1 *)) (C1 * (MetaCons "CommitCommentActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data CreateEvent Source # 

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 # 
Generic CreateEvent Source # 

Associated Types

type Rep CreateEvent :: * -> * #

FromJSON CreateEvent Source # 
NFData CreateEvent Source # 

Methods

rnf :: CreateEvent -> () #

EventHasRepo CreateEvent Source # 
EventHasSender CreateEvent Source # 
type Rep CreateEvent Source # 

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 # 
Data DeleteEvent Source # 

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 # 
Generic DeleteEvent Source # 

Associated Types

type Rep DeleteEvent :: * -> * #

FromJSON DeleteEvent Source # 
NFData DeleteEvent Source # 

Methods

rnf :: DeleteEvent -> () #

EventHasRepo DeleteEvent Source # 
EventHasSender DeleteEvent Source # 
type Rep DeleteEvent Source # 
type Rep DeleteEvent = D1 * (MetaData "DeleteEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "DeleteEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evDeleteRef") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "evDeleteRefType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "evDeletePusherType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OwnerType)) ((:*:) * (S1 * (MetaSel (Just Symbol "evDeleteRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data DeploymentEvent Source # 

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 # 
Generic DeploymentEvent Source # 
FromJSON DeploymentEvent Source # 
NFData DeploymentEvent Source # 

Methods

rnf :: DeploymentEvent -> () #

EventHasRepo DeploymentEvent Source # 
EventHasSender DeploymentEvent Source # 
type Rep DeploymentEvent Source # 
type Rep DeploymentEvent = D1 * (MetaData "DeploymentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "DeploymentEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "evDeploymentInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookDeployment)) ((:*:) * (S1 * (MetaSel (Just Symbol "evDeploymentRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data DeploymentStatusEvent Source # 

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 # 
Generic DeploymentStatusEvent Source # 
FromJSON DeploymentStatusEvent Source # 
NFData DeploymentStatusEvent Source # 

Methods

rnf :: DeploymentStatusEvent -> () #

EventHasRepo DeploymentStatusEvent Source # 
EventHasSender DeploymentStatusEvent Source # 
type Rep DeploymentStatusEvent Source # 
type Rep DeploymentStatusEvent = D1 * (MetaData "DeploymentStatusEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "DeploymentStatusEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evDeplStatusInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookDeploymentStatus)) (S1 * (MetaSel (Just Symbol "evDeplStatusDeployment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookDeployment))) ((:*:) * (S1 * (MetaSel (Just Symbol "evDeplStatusRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data ForkEvent Source # 

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 # 
Generic ForkEvent Source # 

Associated Types

type Rep ForkEvent :: * -> * #

FromJSON ForkEvent Source # 
NFData ForkEvent Source # 

Methods

rnf :: ForkEvent -> () #

EventHasRepo ForkEvent Source # 
EventHasSender ForkEvent Source # 
type Rep ForkEvent Source # 
type Rep ForkEvent = D1 * (MetaData "ForkEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "ForkEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "evForkDestination") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evForkSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data GollumEvent Source # 

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 # 
Generic GollumEvent Source # 

Associated Types

type Rep GollumEvent :: * -> * #

FromJSON GollumEvent Source # 
NFData GollumEvent Source # 

Methods

rnf :: GollumEvent -> () #

EventHasRepo GollumEvent Source # 
EventHasSender GollumEvent Source # 
type Rep GollumEvent Source # 
type Rep GollumEvent = D1 * (MetaData "GollumEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "GollumEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "evGollumPages") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector HookWikiPage))) ((:*:) * (S1 * (MetaSel (Just Symbol "evGollumRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data InstallationEvent Source # 

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 # 
Generic InstallationEvent Source # 
FromJSON InstallationEvent Source # 
NFData InstallationEvent Source # 

Methods

rnf :: InstallationEvent -> () #

EventHasSender InstallationEvent Source # 
type Rep InstallationEvent Source # 
type Rep InstallationEvent = D1 * (MetaData "InstallationEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "InstallationEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "evInstallationAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InstallationEventAction)) ((:*:) * (S1 * (MetaSel (Just Symbol "evInstallationInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookInstallation)) (S1 * (MetaSel (Just Symbol "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 # 
Data InstallationEventAction Source # 

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 # 
Show InstallationEventAction Source # 
Generic InstallationEventAction Source # 
FromJSON InstallationEventAction Source # 
NFData InstallationEventAction Source # 

Methods

rnf :: InstallationEventAction -> () #

type Rep InstallationEventAction Source # 
type Rep InstallationEventAction = D1 * (MetaData "InstallationEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "InstallationCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "InstallationDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "InstallationActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data InstallationRepositoriesEvent Source # 

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 # 
Generic InstallationRepositoriesEvent Source # 
FromJSON InstallationRepositoriesEvent Source # 
NFData InstallationRepositoriesEvent Source # 
EventHasSender InstallationRepositoriesEvent Source # 
type Rep InstallationRepositoriesEvent Source # 
type Rep InstallationRepositoriesEvent = D1 * (MetaData "InstallationRepositoriesEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "InstallationRepositoriesEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evInstallationRepoAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InstallationRepoEventAction)) ((:*:) * (S1 * (MetaSel (Just Symbol "evInstallationRepoInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookInstallation)) (S1 * (MetaSel (Just Symbol "evInstallationRepoSel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "evInstallationReposAdd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector HookRepositorySimple))) ((:*:) * (S1 * (MetaSel (Just Symbol "evInstallationReposRemove") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector HookRepositorySimple))) (S1 * (MetaSel (Just Symbol "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 # 
Data InstallationRepoEventAction Source # 

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 # 
Show InstallationRepoEventAction Source # 
Generic InstallationRepoEventAction Source # 
FromJSON InstallationRepoEventAction Source # 
NFData InstallationRepoEventAction Source # 
type Rep InstallationRepoEventAction Source # 
type Rep InstallationRepoEventAction = D1 * (MetaData "InstallationRepoEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "InstallationRepoCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "InstallationRepoRemovedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "InstallationRepoActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data IssueCommentEvent Source # 

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 # 
Generic IssueCommentEvent Source # 
FromJSON IssueCommentEvent Source # 
NFData IssueCommentEvent Source # 

Methods

rnf :: IssueCommentEvent -> () #

EventHasRepo IssueCommentEvent Source # 
EventHasSender IssueCommentEvent Source # 
type Rep IssueCommentEvent Source # 
type Rep IssueCommentEvent = D1 * (MetaData "IssueCommentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "IssueCommentEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evIssueCommentAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * IssueCommentEventAction)) (S1 * (MetaSel (Just Symbol "evIssueCommentIssue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookIssue))) ((:*:) * (S1 * (MetaSel (Just Symbol "evIssueCommentPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookIssueComment)) ((:*:) * (S1 * (MetaSel (Just Symbol "evIssueCommentRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data IssueCommentEventAction Source # 

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 # 
Show IssueCommentEventAction Source # 
Generic IssueCommentEventAction Source # 
FromJSON IssueCommentEventAction Source # 
NFData IssueCommentEventAction Source # 

Methods

rnf :: IssueCommentEventAction -> () #

type Rep IssueCommentEventAction Source # 
type Rep IssueCommentEventAction = D1 * (MetaData "IssueCommentEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "IssueCommentCreatedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "IssueCommentEditedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "IssueCommentDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "IssueCommentActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data IssuesEvent Source # 

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 # 
Generic IssuesEvent Source # 

Associated Types

type Rep IssuesEvent :: * -> * #

FromJSON IssuesEvent Source # 
NFData IssuesEvent Source # 

Methods

rnf :: IssuesEvent -> () #

EventHasRepo IssuesEvent Source # 
EventHasSender IssuesEvent Source # 
type Rep IssuesEvent Source # 
type Rep IssuesEvent = D1 * (MetaData "IssuesEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "IssuesEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evIssuesEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * IssuesEventAction)) (S1 * (MetaSel (Just Symbol "evIssuesEventIssue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookIssue))) ((:*:) * (S1 * (MetaSel (Just Symbol "evIssuesEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data IssuesEventAction Source # 

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 # 
Show IssuesEventAction Source # 
Generic IssuesEventAction Source # 
FromJSON IssuesEventAction Source # 
NFData IssuesEventAction Source # 

Methods

rnf :: IssuesEventAction -> () #

type Rep IssuesEventAction Source # 
type Rep IssuesEventAction = D1 * (MetaData "IssuesEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "IssuesAssignedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "IssuesUnassignedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "IssuesLabeledAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IssuesUnlabeledAction" PrefixI False) (U1 *)) (C1 * (MetaCons "IssuesOpenedAction" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "IssuesEditedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IssuesMilestonedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "IssuesDemilestonedAction" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "IssuesClosedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "IssuesReopenedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "IssuesActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data LabelEvent Source # 

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 # 
Generic LabelEvent Source # 

Associated Types

type Rep LabelEvent :: * -> * #

FromJSON LabelEvent Source # 
NFData LabelEvent Source # 

Methods

rnf :: LabelEvent -> () #

EventHasRepo LabelEvent Source # 
EventHasSender LabelEvent Source # 
type Rep LabelEvent Source # 
type Rep LabelEvent = D1 * (MetaData "LabelEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "LabelEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evLabelEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * LabelEventAction)) (S1 * (MetaSel (Just Symbol "evLabelEventPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepositoryLabel))) ((:*:) * (S1 * (MetaSel (Just Symbol "evLabelEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evLabelEventOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe HookOrganization))) (S1 * (MetaSel (Just Symbol "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 # 
Data LabelEventAction Source # 

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 # 
Show LabelEventAction Source # 
Generic LabelEventAction Source # 
FromJSON LabelEventAction Source # 
NFData LabelEventAction Source # 

Methods

rnf :: LabelEventAction -> () #

type Rep LabelEventAction Source # 
type Rep LabelEventAction = D1 * (MetaData "LabelEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LabelCreatedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "LabelEditedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LabelDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "LabelActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data MemberEvent Source # 

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 # 
Generic MemberEvent Source # 

Associated Types

type Rep MemberEvent :: * -> * #

FromJSON MemberEvent Source # 
NFData MemberEvent Source # 

Methods

rnf :: MemberEvent -> () #

EventHasRepo MemberEvent Source # 
EventHasSender MemberEvent Source # 
type Rep MemberEvent Source # 
type Rep MemberEvent = D1 * (MetaData "MemberEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "MemberEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evMemberAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MemberEventAction)) (S1 * (MetaSel (Just Symbol "evMemberUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser))) ((:*:) * (S1 * (MetaSel (Just Symbol "evMemberRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data MemberEventAction Source # 

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 # 
Show MemberEventAction Source # 
Generic MemberEventAction Source # 
FromJSON MemberEventAction Source # 
NFData MemberEventAction Source # 

Methods

rnf :: MemberEventAction -> () #

type Rep MemberEventAction Source # 
type Rep MemberEventAction = D1 * (MetaData "MemberEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MemberAddedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "MemberEditedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MemberDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "MemberActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data MembershipEvent Source # 

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 # 
Generic MembershipEvent Source # 
FromJSON MembershipEvent Source # 
NFData MembershipEvent Source # 

Methods

rnf :: MembershipEvent -> () #

EventHasSender MembershipEvent Source # 
type Rep MembershipEvent Source # 
type Rep MembershipEvent = D1 * (MetaData "MembershipEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "MembershipEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evMembershipAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MembershipEventAction)) ((:*:) * (S1 * (MetaSel (Just Symbol "evMembershipScope") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "evMembershipUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser)))) ((:*:) * (S1 * (MetaSel (Just Symbol "evMembershipTeam") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookTeam)) ((:*:) * (S1 * (MetaSel (Just Symbol "evMembershipOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data MembershipEventAction Source # 

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 # 
Show MembershipEventAction Source # 
Generic MembershipEventAction Source # 
FromJSON MembershipEventAction Source # 
NFData MembershipEventAction Source # 

Methods

rnf :: MembershipEventAction -> () #

type Rep MembershipEventAction Source # 
type Rep MembershipEventAction = D1 * (MetaData "MembershipEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "MembershipAddedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MembershipRemovedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "MembershipActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data MilestoneEvent Source # 

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 # 
Generic MilestoneEvent Source # 

Associated Types

type Rep MilestoneEvent :: * -> * #

FromJSON MilestoneEvent Source # 
NFData MilestoneEvent Source # 

Methods

rnf :: MilestoneEvent -> () #

EventHasRepo MilestoneEvent Source # 
EventHasSender MilestoneEvent Source # 
type Rep MilestoneEvent Source # 
type Rep MilestoneEvent = D1 * (MetaData "MilestoneEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "MilestoneEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evMilestoneAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MilestoneEventAction)) (S1 * (MetaSel (Just Symbol "evMilestoenPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookMilestone))) ((:*:) * (S1 * (MetaSel (Just Symbol "evMilestoneRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evMilestoneOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data MilestoneEventAction Source # 

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 # 
Show MilestoneEventAction Source # 
Generic MilestoneEventAction Source # 
FromJSON MilestoneEventAction Source # 
NFData MilestoneEventAction Source # 

Methods

rnf :: MilestoneEventAction -> () #

type Rep MilestoneEventAction Source # 
type Rep MilestoneEventAction = D1 * (MetaData "MilestoneEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "MilestoneCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MilestoneClosedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "MilestoneOpenedAction" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "MilestoneEditedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "MilestoneDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "MilestoneActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data OrganizationEvent Source # 

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 # 
Generic OrganizationEvent Source # 
FromJSON OrganizationEvent Source # 
NFData OrganizationEvent Source # 

Methods

rnf :: OrganizationEvent -> () #

EventHasSender OrganizationEvent Source # 
type Rep OrganizationEvent Source # 
type Rep OrganizationEvent = D1 * (MetaData "OrganizationEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "OrganizationEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evOrganizationAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OrganizationEventAction)) (S1 * (MetaSel (Just Symbol "evOrganizationInvitation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganizationInvitation))) ((:*:) * (S1 * (MetaSel (Just Symbol "evOrganizationMembership") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganizationMembership)) ((:*:) * (S1 * (MetaSel (Just Symbol "evOrganizationOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data OrganizationEventAction Source # 

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 # 
Show OrganizationEventAction Source # 
Generic OrganizationEventAction Source # 
FromJSON OrganizationEventAction Source # 
NFData OrganizationEventAction Source # 

Methods

rnf :: OrganizationEventAction -> () #

type Rep OrganizationEventAction Source # 
type Rep OrganizationEventAction = D1 * (MetaData "OrganizationEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "OrgMemberAddedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "OrgMemberRemovedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OrgMemberInvitedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "OrgActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data OrgBlockEvent Source # 

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 # 
Generic OrgBlockEvent Source # 

Associated Types

type Rep OrgBlockEvent :: * -> * #

FromJSON OrgBlockEvent Source # 
NFData OrgBlockEvent Source # 

Methods

rnf :: OrgBlockEvent -> () #

EventHasSender OrgBlockEvent Source # 
type Rep OrgBlockEvent Source # 
type Rep OrgBlockEvent = D1 * (MetaData "OrgBlockEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "OrgBlockEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evOrgBlockAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * OrgBlockEventAction)) (S1 * (MetaSel (Just Symbol "evOrgBlockUser") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser))) ((:*:) * (S1 * (MetaSel (Just Symbol "evOrgBlockOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data OrgBlockEventAction Source # 

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 # 
Show OrgBlockEventAction Source # 
Generic OrgBlockEventAction Source # 
FromJSON OrgBlockEventAction Source # 
NFData OrgBlockEventAction Source # 

Methods

rnf :: OrgBlockEventAction -> () #

type Rep OrgBlockEventAction Source # 
type Rep OrgBlockEventAction = D1 * (MetaData "OrgBlockEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "OrgBlockBlockedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "OrgBlockUnblockedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "OrgBlockActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data PageBuildEvent Source # 

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 # 
Generic PageBuildEvent Source # 

Associated Types

type Rep PageBuildEvent :: * -> * #

FromJSON PageBuildEvent Source # 
NFData PageBuildEvent Source # 

Methods

rnf :: PageBuildEvent -> () #

EventHasRepo PageBuildEvent Source # 
EventHasSender PageBuildEvent Source # 
type Rep PageBuildEvent Source # 
type Rep PageBuildEvent = D1 * (MetaData "PageBuildEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "PageBuildEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evPageBuildId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "evPageBuildResult") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookPageBuildResult))) ((:*:) * (S1 * (MetaSel (Just Symbol "evPageBuildRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data ProjectCardEvent Source # 

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 # 
Generic ProjectCardEvent Source # 
FromJSON ProjectCardEvent Source # 
NFData ProjectCardEvent Source # 

Methods

rnf :: ProjectCardEvent -> () #

EventHasRepo ProjectCardEvent Source # 
EventHasSender ProjectCardEvent Source # 
type Rep ProjectCardEvent Source # 
type Rep ProjectCardEvent = D1 * (MetaData "ProjectCardEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "ProjectCardEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectCardAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProjectCardEventAction)) (S1 * (MetaSel (Just Symbol "evProjectCardPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookProjectCard))) ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectCardRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectCardOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data ProjectCardEventAction Source # 

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 # 
Show ProjectCardEventAction Source # 
Generic ProjectCardEventAction Source # 
FromJSON ProjectCardEventAction Source # 
NFData ProjectCardEventAction Source # 

Methods

rnf :: ProjectCardEventAction -> () #

type Rep ProjectCardEventAction Source # 
type Rep ProjectCardEventAction = D1 * (MetaData "ProjectCardEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ProjectCardCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ProjectCardEditedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ProjectCardConvertedAction" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ProjectCardMovedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ProjectCardDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ProjectCardActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data ProjectColumnEvent Source # 

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 # 
Generic ProjectColumnEvent Source # 
FromJSON ProjectColumnEvent Source # 
NFData ProjectColumnEvent Source # 

Methods

rnf :: ProjectColumnEvent -> () #

EventHasRepo ProjectColumnEvent Source # 
EventHasSender ProjectColumnEvent Source # 
type Rep ProjectColumnEvent Source # 
type Rep ProjectColumnEvent = D1 * (MetaData "ProjectColumnEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "ProjectColumnEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectColumnAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProjectColumnEventAction)) (S1 * (MetaSel (Just Symbol "evProjectColumnPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookProjectColumn))) ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectColumnRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectColumnOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data ProjectColumnEventAction Source # 

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 # 
Show ProjectColumnEventAction Source # 
Generic ProjectColumnEventAction Source # 
FromJSON ProjectColumnEventAction Source # 
NFData ProjectColumnEventAction Source # 
type Rep ProjectColumnEventAction Source # 
type Rep ProjectColumnEventAction = D1 * (MetaData "ProjectColumnEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ProjectColumnCreatedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ProjectColumnEditedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "ProjectColumnMovedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ProjectColumnDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ProjectColumnActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data ProjectEvent Source # 

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 # 
Generic ProjectEvent Source # 

Associated Types

type Rep ProjectEvent :: * -> * #

FromJSON ProjectEvent Source # 
NFData ProjectEvent Source # 

Methods

rnf :: ProjectEvent -> () #

EventHasRepo ProjectEvent Source # 
EventHasSender ProjectEvent Source # 
type Rep ProjectEvent Source # 
type Rep ProjectEvent = D1 * (MetaData "ProjectEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "ProjectEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ProjectEventAction)) (S1 * (MetaSel (Just Symbol "evProjectPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookProject))) ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evProjectOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data ProjectEventAction Source # 

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 # 
Show ProjectEventAction Source # 
Generic ProjectEventAction Source # 
FromJSON ProjectEventAction Source # 
NFData ProjectEventAction Source # 

Methods

rnf :: ProjectEventAction -> () #

type Rep ProjectEventAction Source # 
type Rep ProjectEventAction = D1 * (MetaData "ProjectEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ProjectCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ProjectEditedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ProjectClosedAction" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ProjectReopenedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ProjectDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ProjectActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data PublicEvent Source # 

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 # 
Generic PublicEvent Source # 

Associated Types

type Rep PublicEvent :: * -> * #

FromJSON PublicEvent Source # 
NFData PublicEvent Source # 

Methods

rnf :: PublicEvent -> () #

EventHasRepo PublicEvent Source # 
EventHasSender PublicEvent Source # 
type Rep PublicEvent Source # 
type Rep PublicEvent = D1 * (MetaData "PublicEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "PublicEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "evPublicEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data PullRequestEvent Source # 

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 # 
Generic PullRequestEvent Source # 
FromJSON PullRequestEvent Source # 
NFData PullRequestEvent Source # 

Methods

rnf :: PullRequestEvent -> () #

EventHasRepo PullRequestEvent Source # 
EventHasSender PullRequestEvent Source # 
type Rep PullRequestEvent Source # 
type Rep PullRequestEvent = D1 * (MetaData "PullRequestEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "PullRequestEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * PullRequestEventAction)) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqNumber") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "evPullReqPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookPullRequest)))) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser)) (S1 * (MetaSel (Just Symbol "evPullReqInstallationId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * 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 # 
Data PullRequestEventAction Source # 

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 # 
Show PullRequestEventAction Source # 
Generic PullRequestEventAction Source # 
FromJSON PullRequestEventAction Source # 
NFData PullRequestEventAction Source # 

Methods

rnf :: PullRequestEventAction -> () #

type Rep PullRequestEventAction Source # 
type Rep PullRequestEventAction = D1 * (MetaData "PullRequestEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PullRequestAssignedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestUnassignedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PullRequestReviewRequestedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PullRequestReviewRequestRemovedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestLabeledAction" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "PullRequestUnlabeledAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PullRequestOpenedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestEditedAction" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "PullRequestClosedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "PullRequestReopenedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data PullRequestReviewEvent Source # 

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 # 
Generic PullRequestReviewEvent Source # 
FromJSON PullRequestReviewEvent Source # 
NFData PullRequestReviewEvent Source # 

Methods

rnf :: PullRequestReviewEvent -> () #

EventHasRepo PullRequestReviewEvent Source # 
EventHasSender PullRequestReviewEvent Source # 
type Rep PullRequestReviewEvent Source # 
type Rep PullRequestReviewEvent = D1 * (MetaData "PullRequestReviewEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "PullRequestReviewEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqReviewAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * PullRequestReviewEventAction)) (S1 * (MetaSel (Just Symbol "evPullReqReviewPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookPullRequestReview))) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqReviewTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookPullRequest)) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqReviewRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data PullRequestReviewEventAction Source # 

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 # 
Show PullRequestReviewEventAction Source # 
Generic PullRequestReviewEventAction Source # 
FromJSON PullRequestReviewEventAction Source # 
NFData PullRequestReviewEventAction Source # 
type Rep PullRequestReviewEventAction Source # 
type Rep PullRequestReviewEventAction = D1 * (MetaData "PullRequestReviewEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PullRequestReviewSubmittedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestReviewEditedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PullRequestReviewDismissedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestReviewActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data PullRequestReviewCommentEvent Source # 

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 # 
Generic PullRequestReviewCommentEvent Source # 
FromJSON PullRequestReviewCommentEvent Source # 
NFData PullRequestReviewCommentEvent Source # 
EventHasRepo PullRequestReviewCommentEvent Source # 
EventHasSender PullRequestReviewCommentEvent Source # 
type Rep PullRequestReviewCommentEvent Source # 
type Rep PullRequestReviewCommentEvent = D1 * (MetaData "PullRequestReviewCommentEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "PullRequestReviewCommentEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqRevComAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * PullRequestReviewCommentEventAction)) (S1 * (MetaSel (Just Symbol "evPullReqRevComment") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookPullRequestReviewComment))) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqRevTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookPullRequest)) ((:*:) * (S1 * (MetaSel (Just Symbol "evPullReqRevRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data PullRequestReviewCommentEventAction Source # 

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 # 
Show PullRequestReviewCommentEventAction Source # 
Generic PullRequestReviewCommentEventAction Source # 
FromJSON PullRequestReviewCommentEventAction Source # 
NFData PullRequestReviewCommentEventAction Source # 
type Rep PullRequestReviewCommentEventAction Source # 
type Rep PullRequestReviewCommentEventAction = D1 * (MetaData "PullRequestReviewCommentEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "PullRequestReviewCommentCreatedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestReviewCommentEditedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "PullRequestReviewCommentDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "PullRequestReviewCommentActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data PushEvent Source # 

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 # 
Generic PushEvent Source # 

Associated Types

type Rep PushEvent :: * -> * #

FromJSON PushEvent Source # 
NFData PushEvent Source # 

Methods

rnf :: PushEvent -> () #

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

data ReleaseEvent Source #

Instances

Eq ReleaseEvent Source # 
Data ReleaseEvent Source # 

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 # 
Generic ReleaseEvent Source # 

Associated Types

type Rep ReleaseEvent :: * -> * #

FromJSON ReleaseEvent Source # 
NFData ReleaseEvent Source # 

Methods

rnf :: ReleaseEvent -> () #

EventHasRepo ReleaseEvent Source # 
EventHasSender ReleaseEvent Source # 
type Rep ReleaseEvent Source # 
type Rep ReleaseEvent = D1 * (MetaData "ReleaseEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "ReleaseEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evReleaseEventAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ReleaseEventAction)) (S1 * (MetaSel (Just Symbol "evReleaseEventPayload") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRelease))) ((:*:) * (S1 * (MetaSel (Just Symbol "evReleaseEventRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data ReleaseEventAction Source # 

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 # 
Show ReleaseEventAction Source # 
Generic ReleaseEventAction Source # 
FromJSON ReleaseEventAction Source # 
NFData ReleaseEventAction Source # 

Methods

rnf :: ReleaseEventAction -> () #

type Rep ReleaseEventAction Source # 
type Rep ReleaseEventAction = D1 * (MetaData "ReleaseEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "ReleasePublishedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "ReleaseActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data RepositoryEvent Source # 

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 # 
Generic RepositoryEvent Source # 
FromJSON RepositoryEvent Source # 
NFData RepositoryEvent Source # 

Methods

rnf :: RepositoryEvent -> () #

EventHasRepo RepositoryEvent Source # 
EventHasSender RepositoryEvent Source # 
type Rep RepositoryEvent Source # 
type Rep RepositoryEvent = D1 * (MetaData "RepositoryEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "RepositoryEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evRepositoryAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * RepositoryEventAction)) (S1 * (MetaSel (Just Symbol "evRepositoryTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository))) ((:*:) * (S1 * (MetaSel (Just Symbol "evRepositoryOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe HookOrganization))) (S1 * (MetaSel (Just Symbol "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 # 
Data RepositoryEventAction Source # 

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 # 
Show RepositoryEventAction Source # 
Generic RepositoryEventAction Source # 
FromJSON RepositoryEventAction Source # 
NFData RepositoryEventAction Source # 

Methods

rnf :: RepositoryEventAction -> () #

type Rep RepositoryEventAction Source # 
type Rep RepositoryEventAction = D1 * (MetaData "RepositoryEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "RepositoryCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "RepositoryDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "RepositoryArchivedAction" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "RepositoryUnarchivedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "RepositoryPublicizedAction" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "RepositoryPrivatizedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "RepositoryActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data StatusEvent Source # 

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 # 
Generic StatusEvent Source # 

Associated Types

type Rep StatusEvent :: * -> * #

FromJSON StatusEvent Source # 
NFData StatusEvent Source # 

Methods

rnf :: StatusEvent -> () #

EventHasRepo StatusEvent Source # 
EventHasSender StatusEvent Source # 
type Rep StatusEvent Source # 
type Rep StatusEvent = D1 * (MetaData "StatusEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "StatusEvent" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)) ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusCommitSha") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "evStatusCommitName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)))) ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusTargetUrl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe URL))) ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "evStatusDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text)))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * StatusEventState)) ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusCommit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookCommit)) (S1 * (MetaSel (Just Symbol "evStatusCreatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)))) ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusUpdatedAt") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * UTCTime)) ((:*:) * (S1 * (MetaSel (Just Symbol "evStatusRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "evStatusSender") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookUser)))))))

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 # 
Data StatusEventState Source # 

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 # 
Show StatusEventState Source # 
Generic StatusEventState Source # 
FromJSON StatusEventState Source # 
NFData StatusEventState Source # 

Methods

rnf :: StatusEventState -> () #

type Rep StatusEventState Source # 
type Rep StatusEventState = D1 * (MetaData "StatusEventState" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "StatusPendingState" PrefixI False) (U1 *)) (C1 * (MetaCons "StatusSuccessState" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "StatusFailureState" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "StatusErrorState" PrefixI False) (U1 *)) (C1 * (MetaCons "StatusStateOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data TeamEvent Source # 

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 # 
Generic TeamEvent Source # 

Associated Types

type Rep TeamEvent :: * -> * #

FromJSON TeamEvent Source # 
NFData TeamEvent Source # 

Methods

rnf :: TeamEvent -> () #

EventHasSender TeamEvent Source # 
type Rep TeamEvent Source # 
type Rep TeamEvent = D1 * (MetaData "TeamEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "TeamEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evTeamAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TeamEventAction)) (S1 * (MetaSel (Just Symbol "evTeamTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookTeam))) ((:*:) * (S1 * (MetaSel (Just Symbol "evTeamOrganization") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data TeamEventAction Source # 

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 # 
Show TeamEventAction Source # 
Generic TeamEventAction Source # 
FromJSON TeamEventAction Source # 
NFData TeamEventAction Source # 

Methods

rnf :: TeamEventAction -> () #

type Rep TeamEventAction Source # 
type Rep TeamEventAction = D1 * (MetaData "TeamEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * ((:+:) * (C1 * (MetaCons "TeamCreatedAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TeamDeletedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "TeamEditedAction" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "TeamAddedToRepoAction" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "TeamRemovedFromRepoAction" PrefixI False) (U1 *)) (C1 * (MetaCons "TeamActionOther" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Data TeamAddEvent Source # 

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 # 
Generic TeamAddEvent Source # 

Associated Types

type Rep TeamAddEvent :: * -> * #

FromJSON TeamAddEvent Source # 
NFData TeamAddEvent Source # 

Methods

rnf :: TeamAddEvent -> () #

EventHasRepo TeamAddEvent Source # 
EventHasSender TeamAddEvent Source # 
type Rep TeamAddEvent Source # 
type Rep TeamAddEvent = D1 * (MetaData "TeamAddEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "TeamAddEvent" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "evTeamAddTarget") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe HookTeam))) (S1 * (MetaSel (Just Symbol "evTeamAddRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository))) ((:*:) * (S1 * (MetaSel (Just Symbol "evTeamAddOrg") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookOrganization)) (S1 * (MetaSel (Just Symbol "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 # 
Data WatchEvent Source # 

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 # 
Generic WatchEvent Source # 

Associated Types

type Rep WatchEvent :: * -> * #

FromJSON WatchEvent Source # 
NFData WatchEvent Source # 

Methods

rnf :: WatchEvent -> () #

EventHasRepo WatchEvent Source # 
EventHasSender WatchEvent Source # 
type Rep WatchEvent Source # 
type Rep WatchEvent = D1 * (MetaData "WatchEvent" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) (C1 * (MetaCons "WatchEvent" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "evWatchAction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * WatchEventAction)) ((:*:) * (S1 * (MetaSel (Just Symbol "evWatchRepo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * HookRepository)) (S1 * (MetaSel (Just Symbol "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 # 
Data WatchEventAction Source # 

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 # 
Show WatchEventAction Source # 
Generic WatchEventAction Source # 
FromJSON WatchEventAction Source # 
NFData WatchEventAction Source # 

Methods

rnf :: WatchEventAction -> () #

type Rep WatchEventAction Source # 
type Rep WatchEventAction = D1 * (MetaData "WatchEventAction" "GitHub.Data.Webhooks.Events" "github-webhooks-0.9.1-7P2E3KAsViZ2U65BdI4PdH" False) ((:+:) * (C1 * (MetaCons "WatchStartedAction" PrefixI False) (U1 *)) (C1 * (MetaCons "WatchActionOther" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))