{-# LANGUAGE Trustworthy #-}
module GitHub.Data.Webhooks.Events
( EventHasSender(..)
, EventHasRepo(..)
, CommitCommentEvent(..)
, CommitCommentEventAction(..)
, CreateEvent(..)
, DeleteEvent(..)
, DeploymentEvent(..)
, DeploymentStatusEvent(..)
, DownloadEvent(..)
, FollowEvent(..)
, ForkEvent(..)
, ForkApplyEvent(..)
, GistEvent(..)
, GollumEvent(..)
, InstallationEvent(..)
, InstallationEventAction(..)
, InstallationRepositoriesEvent(..)
, InstallationRepoEventAction(..)
, IssueCommentEvent(..)
, IssueCommentEventAction(..)
, IssuesEvent(..)
, IssuesEventAction(..)
, LabelEvent(..)
, LabelEventAction(..)
, MemberEvent(..)
, MemberEventAction(..)
, MembershipEvent(..)
, MembershipEventAction(..)
, MilestoneEvent(..)
, MilestoneEventAction(..)
, OrganizationEvent(..)
, OrganizationEventAction(..)
, OrgBlockEvent(..)
, OrgBlockEventAction(..)
, PageBuildEvent(..)
, ProjectCardEvent(..)
, ProjectCardEventAction(..)
, ProjectColumnEvent(..)
, ProjectColumnEventAction(..)
, ProjectEvent(..)
, ProjectEventAction(..)
, PublicEvent(..)
, PullRequestEvent(..)
, PullRequestEventAction(..)
, PullRequestReviewEvent(..)
, PullRequestReviewEventAction(..)
, PullRequestReviewCommentEvent(..)
, PullRequestReviewCommentEventAction(..)
, PushEvent(..)
, ReleaseEvent(..)
, ReleaseEventAction(..)
, RepositoryEvent(..)
, RepositoryEventAction(..)
, StatusEvent(..)
, StatusEventState(..)
, TeamEvent(..)
, TeamEventAction(..)
, TeamAddEvent(..)
, WatchEvent(..)
, WatchEventAction(..)
) where
import Data.Aeson (FromJSON(..), withObject, withText, (.:), (.:?), (.!=))
import Control.DeepSeq (NFData(..))
import Control.DeepSeq.Generics (genericRnf)
import Data.Data (Data, Typeable)
import Data.Time (UTCTime)
import Data.Text (Text)
import Data.Vector (Vector)
import GHC.Generics (Generic)
import GitHub.Data.Webhooks.Payload
class EventHasSender eventKind where
senderOfEvent :: eventKind -> HookUser
class EventHasRepo eventKind where
repoForEvent :: eventKind -> HookRepository
data CommitCommentEventAction
= CommitCommentActionCreated
| CommitCommentActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData CommitCommentEventAction where rnf = genericRnf
instance FromJSON CommitCommentEventAction where
parseJSON = withText "Commit comment event action" $ \t ->
case t of
"created" -> pure CommitCommentActionCreated
_ -> pure (CommitCommentActionOther t)
data CommitCommentEvent = CommitCommentEvent
{ evCommitCommentAction :: !CommitCommentEventAction
, evCommitCommentPayload :: !HookCommitComment
, evCommitCommentRepo :: !HookRepository
, evCommitCommentSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender CommitCommentEvent where senderOfEvent = evCommitCommentSender
instance EventHasRepo CommitCommentEvent where repoForEvent = evCommitCommentRepo
instance NFData CommitCommentEvent where rnf = genericRnf
data CreateEvent = CreateEvent
{ evCreateRef :: !Text
, evCreateRefType :: !Text
, evCreateMasterBranch :: !Text
, evCreateDescription :: !Text
, evCreatePusherType :: !OwnerType
, evCreateRepo :: !HookRepository
, evCreateSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender CreateEvent where senderOfEvent = evCreateSender
instance EventHasRepo CreateEvent where repoForEvent = evCreateRepo
instance NFData CreateEvent where rnf = genericRnf
data DeleteEvent = DeleteEvent
{ evDeleteRef :: !Text
, evDeleteRefType :: !Text
, evDeletePusherType :: !OwnerType
, evDeleteRepo :: !HookRepository
, evDeleteSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender DeleteEvent where senderOfEvent = evDeleteSender
instance EventHasRepo DeleteEvent where repoForEvent = evDeleteRepo
instance NFData DeleteEvent where rnf = genericRnf
data DeploymentEvent = DeploymentEvent
{ evDeploymentInfo :: !HookDeployment
, evDeploymentRepo :: !HookRepository
, evDeploymentSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender DeploymentEvent where senderOfEvent = evDeploymentSender
instance EventHasRepo DeploymentEvent where repoForEvent = evDeploymentRepo
instance NFData DeploymentEvent where rnf = genericRnf
data DeploymentStatusEvent = DeploymentStatusEvent
{ evDeplStatusInfo :: !HookDeploymentStatus
, evDeplStatusDeployment :: !HookDeployment
, evDeplStatusRepo :: !HookRepository
, evDeplStatusSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender DeploymentStatusEvent where senderOfEvent = evDeplStatusSender
instance EventHasRepo DeploymentStatusEvent where repoForEvent = evDeplStatusRepo
instance NFData DeploymentStatusEvent where rnf = genericRnf
data DownloadEvent = DownloadEvent
data FollowEvent = FollowEvent
data ForkEvent = ForkEvent
{ evForkDestination :: !HookRepository
, evForkSource :: !HookRepository
, evForkSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender ForkEvent where senderOfEvent = evForkSender
instance EventHasRepo ForkEvent where repoForEvent = evForkSource
instance NFData ForkEvent where rnf = genericRnf
data ForkApplyEvent = ForkApplyEvent
data GistEvent = GistEvent
data GollumEvent = GollumEvent
{ evGollumPages :: !(Vector HookWikiPage)
, evGollumRepo :: !HookRepository
, evGollumSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender GollumEvent where senderOfEvent = evGollumSender
instance EventHasRepo GollumEvent where repoForEvent = evGollumRepo
instance NFData GollumEvent where rnf = genericRnf
data InstallationEventAction
= InstallationCreatedAction
| InstallationDeletedAction
| InstallationActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData InstallationEventAction where rnf = genericRnf
instance FromJSON InstallationEventAction where
parseJSON = withText "Installation event action" $ \t ->
case t of
"created" -> pure InstallationCreatedAction
"deleted" -> pure InstallationDeletedAction
_ -> pure (InstallationActionOther t)
data InstallationEvent = InstallationEvent
{ evInstallationAction :: !InstallationEventAction
, evInstallationInfo :: !HookInstallation
, evInstallationRepos :: !(Vector HookRepositorySimple)
, evInstallationSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender InstallationEvent where senderOfEvent = evInstallationSender
instance NFData InstallationEvent where rnf = genericRnf
data InstallationRepoEventAction
= InstallationRepoCreatedAction
| InstallationRepoRemovedAction
| InstallationRepoActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData InstallationRepoEventAction where rnf = genericRnf
instance FromJSON InstallationRepoEventAction where
parseJSON = withText "Installation repo event action" $ \t ->
case t of
"created" -> pure InstallationRepoCreatedAction
"removed" -> pure InstallationRepoRemovedAction
_ -> pure (InstallationRepoActionOther t)
data InstallationRepositoriesEvent = InstallationRepositoriesEvent
{ evInstallationRepoAction :: !InstallationRepoEventAction
, evInstallationRepoInfo :: !HookInstallation
, evInstallationRepoSel :: !Text
, evInstallationReposAdd :: !(Vector HookRepositorySimple)
, evInstallationReposRemove :: !(Vector HookRepositorySimple)
, evInstallationReposSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender InstallationRepositoriesEvent where senderOfEvent = evInstallationReposSender
instance NFData InstallationRepositoriesEvent where rnf = genericRnf
data IssueCommentEventAction
= IssueCommentCreatedAction
| IssueCommentEditedAction
| IssueCommentDeletedAction
| IssueCommentActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData IssueCommentEventAction where rnf = genericRnf
instance FromJSON IssueCommentEventAction where
parseJSON = withText "Issue comment event action" $ \t ->
case t of
"created" -> pure IssueCommentCreatedAction
"edited" -> pure IssueCommentEditedAction
"deleted" -> pure IssueCommentDeletedAction
_ -> pure (IssueCommentActionOther t)
data IssueCommentEvent = IssueCommentEvent
{ evIssueCommentAction :: !IssueCommentEventAction
, evIssueCommentIssue :: !HookIssue
, evIssueCommentPayload :: !HookIssueComment
, evIssueCommentRepo :: !HookRepository
, evIssueCommentSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender IssueCommentEvent where senderOfEvent = evIssueCommentSender
instance EventHasRepo IssueCommentEvent where repoForEvent = evIssueCommentRepo
instance NFData IssueCommentEvent where rnf = genericRnf
data IssuesEventAction
= IssuesAssignedAction
| IssuesUnassignedAction
| IssuesLabeledAction
| IssuesUnlabeledAction
| IssuesOpenedAction
| IssuesEditedAction
| IssuesMilestonedAction
| IssuesDemilestonedAction
| IssuesClosedAction
| IssuesReopenedAction
| IssuesActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData IssuesEventAction where rnf = genericRnf
instance FromJSON IssuesEventAction where
parseJSON = withText "Issue comment event action" $ \t ->
case t of
"assigned" -> pure IssuesAssignedAction
"unassigned" -> pure IssuesUnassignedAction
"labeled" -> pure IssuesLabeledAction
"unlabeled" -> pure IssuesUnlabeledAction
"opened" -> pure IssuesOpenedAction
"edited" -> pure IssuesEditedAction
"milestoned" -> pure IssuesMilestonedAction
"demilestoned" -> pure IssuesDemilestonedAction
"closed" -> pure IssuesClosedAction
"reopened" -> pure IssuesReopenedAction
_ -> pure (IssuesActionOther t)
data IssuesEvent = IssuesEvent
{ evIssuesEventAction :: !IssuesEventAction
, evIssuesEventIssue :: !HookIssue
, evIssuesEventRepo :: !HookRepository
, evIssuesEventSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender IssuesEvent where senderOfEvent = evIssuesEventSender
instance EventHasRepo IssuesEvent where repoForEvent = evIssuesEventRepo
instance NFData IssuesEvent where rnf = genericRnf
data LabelEventAction
= LabelCreatedAction
| LabelEditedAction
| LabelDeletedAction
| LabelActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData LabelEventAction where rnf = genericRnf
instance FromJSON LabelEventAction where
parseJSON = withText "Label event action" $ \t ->
case t of
"created" -> pure LabelCreatedAction
"edited" -> pure LabelEditedAction
"deleted" -> pure LabelDeletedAction
_ -> pure (LabelActionOther t)
data LabelEvent = LabelEvent
{ evLabelEventAction :: !LabelEventAction
, evLabelEventPayload :: !HookRepositoryLabel
, evLabelEventRepo :: !HookRepository
, evLabelEventOrganization :: !(Maybe HookOrganization)
, evLabelEventSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender LabelEvent where senderOfEvent = evLabelEventSender
instance EventHasRepo LabelEvent where repoForEvent = evLabelEventRepo
instance NFData LabelEvent where rnf = genericRnf
data MemberEventAction
= MemberAddedAction
| MemberEditedAction
| MemberDeletedAction
| MemberActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData MemberEventAction where rnf = genericRnf
instance FromJSON MemberEventAction where
parseJSON = withText "Member event action" $ \t ->
case t of
"added" -> pure MemberAddedAction
"edited" -> pure MemberEditedAction
"deleted" -> pure MemberDeletedAction
_ -> pure (MemberActionOther t)
data MemberEvent = MemberEvent
{ evMemberAction :: !MemberEventAction
, evMemberUser :: !HookUser
, evMemberRepo :: !HookRepository
, evMemberSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender MemberEvent where senderOfEvent = evMemberSender
instance EventHasRepo MemberEvent where repoForEvent = evMemberRepo
instance NFData MemberEvent where rnf = genericRnf
data MembershipEventAction
= MembershipAddedAction
| MembershipRemovedAction
| MembershipActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData MembershipEventAction where rnf = genericRnf
instance FromJSON MembershipEventAction where
parseJSON = withText "Membership event action" $ \t ->
case t of
"added" -> pure MembershipAddedAction
"removed" -> pure MembershipRemovedAction
_ -> pure (MembershipActionOther t)
data MembershipEvent = MembershipEvent
{ evMembershipAction :: !MembershipEventAction
, evMembershipScope :: !Text
, evMembershipUser :: !HookUser
, evMembershipTeam :: !HookTeam
, evMembershipOrg :: !HookOrganization
, evMembershipSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender MembershipEvent where senderOfEvent = evMembershipSender
instance NFData MembershipEvent where rnf = genericRnf
data MilestoneEventAction
= MilestoneCreatedAction
| MilestoneClosedAction
| MilestoneOpenedAction
| MilestoneEditedAction
| MilestoneDeletedAction
| MilestoneActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData MilestoneEventAction where rnf = genericRnf
instance FromJSON MilestoneEventAction where
parseJSON = withText "Milestone event action" $ \t ->
case t of
"created" -> pure MilestoneCreatedAction
"closed" -> pure MilestoneClosedAction
"opened" -> pure MilestoneOpenedAction
"edited" -> pure MilestoneEditedAction
"deleted" -> pure MilestoneDeletedAction
_ -> pure (MilestoneActionOther t)
data MilestoneEvent = MilestoneEvent
{ evMilestoneAction :: !MilestoneEventAction
, evMilestoenPayload :: !HookMilestone
, evMilestoneRepo :: !HookRepository
, evMilestoneOrg :: !HookOrganization
, evMilestoneSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender MilestoneEvent where senderOfEvent = evMilestoneSender
instance EventHasRepo MilestoneEvent where repoForEvent = evMilestoneRepo
instance NFData MilestoneEvent where rnf = genericRnf
data OrganizationEventAction
= OrgMemberAddedAction
| OrgMemberRemovedAction
| OrgMemberInvitedAction
| OrgActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData OrganizationEventAction where rnf = genericRnf
instance FromJSON OrganizationEventAction where
parseJSON = withText "Organization event action" $ \t ->
case t of
"member_added" -> pure OrgMemberAddedAction
"member_removed" -> pure OrgMemberRemovedAction
"member_invited" -> pure OrgMemberInvitedAction
_ -> pure (OrgActionOther t)
data OrganizationEvent = OrganizationEvent
{ evOrganizationAction :: !OrganizationEventAction
, evOrganizationInvitation :: !HookOrganizationInvitation
, evOrganizationMembership :: !HookOrganizationMembership
, evOrganizationOrg :: !HookOrganization
, evOrganizationSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender OrganizationEvent where senderOfEvent = evOrganizationSender
instance NFData OrganizationEvent where rnf = genericRnf
data OrgBlockEventAction
= OrgBlockBlockedAction
| OrgBlockUnblockedAction
| OrgBlockActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData OrgBlockEventAction where rnf = genericRnf
instance FromJSON OrgBlockEventAction where
parseJSON = withText "Organization event action" $ \t ->
case t of
"blocked" -> pure OrgBlockBlockedAction
"unblocked" -> pure OrgBlockUnblockedAction
_ -> pure (OrgBlockActionOther t)
data OrgBlockEvent = OrgBlockEvent
{ evOrgBlockAction :: !OrgBlockEventAction
, evOrgBlockUser :: !HookUser
, evOrgBlockOrg :: !HookOrganization
, evOrgBlockSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender OrgBlockEvent where senderOfEvent = evOrgBlockSender
instance NFData OrgBlockEvent where rnf = genericRnf
data PageBuildEvent = PageBuildEvent
{ evPageBuildId :: !Int
, evPageBuildResult :: !HookPageBuildResult
, evPageBuildRepo :: !HookRepository
, evPageBuildSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender PageBuildEvent where senderOfEvent = evPageBuildSender
instance EventHasRepo PageBuildEvent where repoForEvent = evPageBuildRepo
instance NFData PageBuildEvent where rnf = genericRnf
data ProjectCardEventAction
= ProjectCardCreatedAction
| ProjectCardEditedAction
| ProjectCardConvertedAction
| ProjectCardMovedAction
| ProjectCardDeletedAction
| ProjectCardActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData ProjectCardEventAction where rnf = genericRnf
instance FromJSON ProjectCardEventAction where
parseJSON = withText "Project card event action" $ \t ->
case t of
"created" -> pure ProjectCardCreatedAction
"edited" -> pure ProjectCardEditedAction
"converted" -> pure ProjectCardConvertedAction
"moved" -> pure ProjectCardMovedAction
"deleted" -> pure ProjectCardDeletedAction
_ -> pure (ProjectCardActionOther t)
data ProjectCardEvent = ProjectCardEvent
{ evProjectCardAction :: !ProjectCardEventAction
, evProjectCardPayload :: !HookProjectCard
, evProjectCardRepo :: !HookRepository
, evProjectCardOrg :: !HookOrganization
, evProjectCardSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender ProjectCardEvent where senderOfEvent = evProjectCardSender
instance EventHasRepo ProjectCardEvent where repoForEvent = evProjectCardRepo
instance NFData ProjectCardEvent where rnf = genericRnf
data ProjectColumnEventAction
= ProjectColumnCreatedAction
| ProjectColumnEditedAction
| ProjectColumnMovedAction
| ProjectColumnDeletedAction
| ProjectColumnActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData ProjectColumnEventAction where rnf = genericRnf
instance FromJSON ProjectColumnEventAction where
parseJSON = withText "Project column event action" $ \t ->
case t of
"created" -> pure ProjectColumnCreatedAction
"edited" -> pure ProjectColumnEditedAction
"moved" -> pure ProjectColumnMovedAction
"deleted" -> pure ProjectColumnDeletedAction
_ -> pure (ProjectColumnActionOther t)
data ProjectColumnEvent = ProjectColumnEvent
{ evProjectColumnAction :: !ProjectColumnEventAction
, evProjectColumnPayload :: !HookProjectColumn
, evProjectColumnRepo :: !HookRepository
, evProjectColumnOrg :: !HookOrganization
, evProjectColumnSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender ProjectColumnEvent where senderOfEvent = evProjectColumnSender
instance EventHasRepo ProjectColumnEvent where repoForEvent = evProjectColumnRepo
instance NFData ProjectColumnEvent where rnf = genericRnf
data ProjectEventAction
= ProjectCreatedAction
| ProjectEditedAction
| ProjectClosedAction
| ProjectReopenedAction
| ProjectDeletedAction
| ProjectActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData ProjectEventAction where rnf = genericRnf
instance FromJSON ProjectEventAction where
parseJSON = withText "Project event action" $ \t ->
case t of
"created" -> pure ProjectCreatedAction
"edited" -> pure ProjectEditedAction
"closed" -> pure ProjectClosedAction
"reopened" -> pure ProjectReopenedAction
"deleted" -> pure ProjectDeletedAction
_ -> pure (ProjectActionOther t)
data ProjectEvent = ProjectEvent
{ evProjectEventAction :: !ProjectEventAction
, evProjectPayload :: !HookProject
, evProjectRepo :: !HookRepository
, evProjectOrganization :: !HookOrganization
, evProjectSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender ProjectEvent where senderOfEvent = evProjectSender
instance EventHasRepo ProjectEvent where repoForEvent = evProjectRepo
instance NFData ProjectEvent where rnf = genericRnf
data PublicEvent = PublicEvent
{ evPublicEventRepo :: !HookRepository
, evPublicEventSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender PublicEvent where senderOfEvent = evPublicEventSender
instance EventHasRepo PublicEvent where repoForEvent = evPublicEventRepo
instance NFData PublicEvent where rnf = genericRnf
data PullRequestEventAction
= PullRequestAssignedAction
| PullRequestUnassignedAction
| PullRequestReviewRequestedAction
| PullRequestReviewRequestRemovedAction
| PullRequestLabeledAction
| PullRequestUnlabeledAction
| PullRequestOpenedAction
| PullRequestEditedAction
| PullRequestClosedAction
| PullRequestReopenedAction
| PullRequestActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData PullRequestEventAction where rnf = genericRnf
instance FromJSON PullRequestEventAction where
parseJSON = withText "Pull request event action" $ \t ->
case t of
"assigned" -> pure PullRequestAssignedAction
"unassigned" -> pure PullRequestUnassignedAction
"review_requsted" -> pure PullRequestReviewRequestedAction
"review_request_removed" -> pure PullRequestReviewRequestRemovedAction
"labeled" -> pure PullRequestLabeledAction
"unlabeled" -> pure PullRequestUnlabeledAction
"opened" -> pure PullRequestOpenedAction
"edited" -> pure PullRequestEditedAction
"closed" -> pure PullRequestClosedAction
"reopened" -> pure PullRequestReopenedAction
_ -> pure (PullRequestActionOther t)
data PullRequestEvent = PullRequestEvent
{ evPullReqAction :: !PullRequestEventAction
, evPullReqNumber :: !Int
, evPullReqPayload :: !HookPullRequest
, evPullReqRepo :: !HookRepository
, evPullReqSender :: !HookUser
, evPullReqInstallationId :: !(Maybe Int)
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender PullRequestEvent where senderOfEvent = evPullReqSender
instance EventHasRepo PullRequestEvent where repoForEvent = evPullReqRepo
instance NFData PullRequestEvent where rnf = genericRnf
data PullRequestReviewEventAction
= PullRequestReviewSubmittedAction
| PullRequestReviewEditedAction
| PullRequestReviewDismissedAction
| PullRequestReviewActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData PullRequestReviewEventAction where rnf = genericRnf
instance FromJSON PullRequestReviewEventAction where
parseJSON = withText "Pull request review event action" $ \t ->
case t of
"submitted" -> pure PullRequestReviewSubmittedAction
"edited" -> pure PullRequestReviewEditedAction
"dismissed" -> pure PullRequestReviewDismissedAction
_ -> pure (PullRequestReviewActionOther t)
data PullRequestReviewEvent = PullRequestReviewEvent
{ evPullReqReviewAction :: !PullRequestReviewEventAction
, evPullReqReviewPayload :: !HookPullRequestReview
, evPullReqReviewTarget :: !HookPullRequest
, evPullReqReviewRepo :: !HookRepository
, evPullReqReviewSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender PullRequestReviewEvent where senderOfEvent = evPullReqReviewSender
instance EventHasRepo PullRequestReviewEvent where repoForEvent = evPullReqReviewRepo
instance NFData PullRequestReviewEvent where rnf = genericRnf
data PullRequestReviewCommentEventAction
= PullRequestReviewCommentCreatedAction
| PullRequestReviewCommentEditedAction
| PullRequestReviewCommentDeletedAction
| PullRequestReviewCommentActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData PullRequestReviewCommentEventAction where rnf = genericRnf
instance FromJSON PullRequestReviewCommentEventAction where
parseJSON = withText "Pull request review comment event action" $ \t ->
case t of
"created" -> pure PullRequestReviewCommentCreatedAction
"edited" -> pure PullRequestReviewCommentEditedAction
"deleted" -> pure PullRequestReviewCommentDeletedAction
_ -> pure (PullRequestReviewCommentActionOther t)
data PullRequestReviewCommentEvent = PullRequestReviewCommentEvent
{ evPullReqRevComAction :: !PullRequestReviewCommentEventAction
, evPullReqRevComment :: !HookPullRequestReviewComment
, evPullReqRevTarget :: !HookPullRequest
, evPullReqRevRepo :: !HookRepository
, evPullReqRevSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender PullRequestReviewCommentEvent where senderOfEvent = evPullReqRevSender
instance EventHasRepo PullRequestReviewCommentEvent where repoForEvent = evPullReqRevRepo
instance NFData PullRequestReviewCommentEvent where rnf = genericRnf
data PushEvent = PushEvent
{ evPushRef :: !Text
, evPushHeadSha :: !(Maybe Text)
, evPushBeforeSha :: !(Maybe Text)
, evPushCreated :: !Bool
, evPushDeleted :: !Bool
, evPushForced :: !Bool
, evPushBaseRef :: !(Maybe Text)
, evPushCompareUrl :: !URL
, evPushCommits :: !(Maybe (Vector HookCommit))
, evPushHeadCommit :: !(Maybe HookCommit)
, evPushRepository :: !HookRepository
, evPushOrganization :: !(Maybe HookOrganization)
, evPushSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender PushEvent where senderOfEvent = evPushSender
instance EventHasRepo PushEvent where repoForEvent = evPushRepository
instance NFData PushEvent where rnf = genericRnf
data ReleaseEventAction
= ReleasePublishedAction
| ReleaseActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData ReleaseEventAction where rnf = genericRnf
instance FromJSON ReleaseEventAction where
parseJSON = withText "Release event action" $ \t ->
case t of
"published" -> pure ReleasePublishedAction
_ -> pure (ReleaseActionOther t)
data ReleaseEvent = ReleaseEvent
{ evReleaseEventAction :: !ReleaseEventAction
, evReleaseEventPayload :: !HookRelease
, evReleaseEventRepo :: !HookRepository
, evReleaseEventSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender ReleaseEvent where senderOfEvent = evReleaseEventSender
instance EventHasRepo ReleaseEvent where repoForEvent = evReleaseEventRepo
instance NFData ReleaseEvent where rnf = genericRnf
data RepositoryEventAction
= RepositoryCreatedAction
| RepositoryDeletedAction
| RepositoryArchivedAction
| RepositoryUnarchivedAction
| RepositoryPublicizedAction
| RepositoryPrivatizedAction
| RepositoryActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData RepositoryEventAction where rnf = genericRnf
instance FromJSON RepositoryEventAction where
parseJSON = withText "Repository event action" $ \t ->
case t of
"created" -> pure RepositoryCreatedAction
"deleted" -> pure RepositoryDeletedAction
"archived" -> pure RepositoryArchivedAction
"unarchived" -> pure RepositoryUnarchivedAction
"publicized" -> pure RepositoryPublicizedAction
"privatized" -> pure RepositoryPrivatizedAction
_ -> pure (RepositoryActionOther t)
data RepositoryEvent = RepositoryEvent
{ evRepositoryAction :: !RepositoryEventAction
, evRepositoryTarget :: !HookRepository
, evRepositoryOrg :: !(Maybe HookOrganization)
, evRepositorySender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender RepositoryEvent where senderOfEvent = evRepositorySender
instance EventHasRepo RepositoryEvent where repoForEvent = evRepositoryTarget
instance NFData RepositoryEvent where rnf = genericRnf
data StatusEventState
= StatusPendingState
| StatusSuccessState
| StatusFailureState
| StatusErrorState
| StatusStateOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData StatusEventState where rnf = genericRnf
instance FromJSON StatusEventState where
parseJSON = withText "Status event state" $ \t ->
case t of
"pending" -> pure StatusPendingState
"success" -> pure StatusSuccessState
"failure" -> pure StatusFailureState
"error" -> pure StatusErrorState
_ -> pure (StatusStateOther t)
data StatusEvent = StatusEvent
{ evStatusId :: !Int
, evStatusCommitSha :: !Text
, evStatusCommitName :: !Text
, evStatusTargetUrl :: !(Maybe URL)
, evStatusContext :: !Text
, evStatusDescription :: !(Maybe Text)
, evStatusState :: !StatusEventState
, evStatusCommit :: !HookCommit
, evStatusCreatedAt :: !UTCTime
, evStatusUpdatedAt :: !UTCTime
, evStatusRepo :: !HookRepository
, evStatusSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender StatusEvent where senderOfEvent = evStatusSender
instance EventHasRepo StatusEvent where repoForEvent = evStatusRepo
instance NFData StatusEvent where rnf = genericRnf
data TeamEventAction
= TeamCreatedAction
| TeamDeletedAction
| TeamEditedAction
| TeamAddedToRepoAction
| TeamRemovedFromRepoAction
| TeamActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData TeamEventAction where rnf = genericRnf
instance FromJSON TeamEventAction where
parseJSON = withText "Team event action" $ \t ->
case t of
"created" -> pure TeamCreatedAction
"deleted" -> pure TeamDeletedAction
"edited" -> pure TeamEditedAction
"added_to_repository" -> pure TeamAddedToRepoAction
"removed_from_repository" -> pure TeamRemovedFromRepoAction
_ -> pure (TeamActionOther t)
data TeamEvent = TeamEvent
{ evTeamAction :: !TeamEventAction
, evTeamTarget :: !HookTeam
, evTeamOrganization :: !HookOrganization
, evTeamSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender TeamEvent where senderOfEvent = evTeamSender
instance NFData TeamEvent where rnf = genericRnf
data TeamAddEvent = TeamAddEvent
{ evTeamAddTarget :: !(Maybe HookTeam)
, evTeamAddRepo :: !HookRepository
, evTeamAddOrg :: !HookOrganization
, evTeamAddSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender TeamAddEvent where senderOfEvent = evTeamAddSender
instance EventHasRepo TeamAddEvent where repoForEvent = evTeamAddRepo
instance NFData TeamAddEvent where rnf = genericRnf
data WatchEventAction
= WatchStartedAction
| WatchActionOther !Text
deriving (Eq, Ord, Show, Generic, Typeable, Data)
instance NFData WatchEventAction where rnf = genericRnf
instance FromJSON WatchEventAction where
parseJSON = withText "Watch event action" $ \t ->
case t of
"started" -> pure WatchStartedAction
_ -> pure (WatchActionOther t)
data WatchEvent = WatchEvent
{ evWatchAction :: !WatchEventAction
, evWatchRepo :: !HookRepository
, evWatchSender :: !HookUser
}
deriving (Eq, Show, Typeable, Data, Generic)
instance EventHasSender WatchEvent where senderOfEvent = evWatchSender
instance EventHasRepo WatchEvent where repoForEvent = evWatchRepo
instance NFData WatchEvent where rnf = genericRnf
instance FromJSON CommitCommentEvent where
parseJSON = withObject "CommitCommentEvent" $ \o -> CommitCommentEvent
<$> o .: "action"
<*> o .: "comment"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON CreateEvent where
parseJSON = withObject "CreateEvent" $ \o -> CreateEvent
<$> o .: "ref"
<*> o .: "ref_type"
<*> o .: "master_branch"
<*> o .: "description"
<*> o .: "pusher_type"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON DeleteEvent where
parseJSON = withObject "DeleteEvent" $ \o -> DeleteEvent
<$> o .: "ref"
<*> o .: "ref_type"
<*> o .: "pusher_type"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON DeploymentEvent where
parseJSON = withObject "DeploymentEvent" $ \o -> DeploymentEvent
<$> o .: "deployment"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON DeploymentStatusEvent where
parseJSON = withObject "DeploymentStatusEvent" $ \o -> DeploymentStatusEvent
<$> o .: "deployment_status"
<*> o .: "deployment"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON ForkEvent where
parseJSON = withObject "ForkEvent" $ \o -> ForkEvent
<$> o .: "forkee"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON GollumEvent where
parseJSON = withObject "GollumEvent" $ \o -> GollumEvent
<$> o .: "pages"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON InstallationEvent where
parseJSON = withObject "InstallationEvent" $ \o -> InstallationEvent
<$> o .: "action"
<*> o .: "installation"
<*> o .:? "repositories" .!= mempty
<*> o .: "sender"
instance FromJSON InstallationRepositoriesEvent where
parseJSON = withObject "InstallationRepositoriesEvent" $ \o -> InstallationRepositoriesEvent
<$> o .: "action"
<*> o .: "installation"
<*> o .: "repository_selection"
<*> o .: "repositories_added"
<*> o .: "repositories_removed"
<*> o .: "sender"
instance FromJSON IssueCommentEvent where
parseJSON = withObject "IssueCommentEvent" $ \o -> IssueCommentEvent
<$> o .: "action"
<*> o .: "issue"
<*> o .: "comment"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON IssuesEvent where
parseJSON = withObject "IssuesEvent" $ \o -> IssuesEvent
<$> o .: "action"
<*> o .: "issue"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON LabelEvent where
parseJSON = withObject "LabelEvent" $ \o -> LabelEvent
<$> o .: "action"
<*> o .: "label"
<*> o .: "repository"
<*> o .:? "organization"
<*> o .: "sender"
instance FromJSON MemberEvent where
parseJSON = withObject "MemberEvent" $ \o -> MemberEvent
<$> o .: "action"
<*> o .: "member"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON MembershipEvent where
parseJSON = withObject "MembershipEvent" $ \o -> MembershipEvent
<$> o .: "action"
<*> o .: "scope"
<*> o .: "member"
<*> o .: "team"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON MilestoneEvent where
parseJSON = withObject "MilestoneEvent" $ \o -> MilestoneEvent
<$> o .: "action"
<*> o .: "milestone"
<*> o .: "repository"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON OrganizationEvent where
parseJSON = withObject "OrganizationEvent" $ \o -> OrganizationEvent
<$> o .: "action"
<*> o .: "invitation"
<*> o .: "membership"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON OrgBlockEvent where
parseJSON = withObject "OrgBlockEvent" $ \o -> OrgBlockEvent
<$> o .: "action"
<*> o .: "blocked_user"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON PageBuildEvent where
parseJSON = withObject "PageBuildEvent" $ \o -> PageBuildEvent
<$> o .: "id"
<*> o .: "build"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON ProjectCardEvent where
parseJSON = withObject "ProjectCardEvent" $ \o -> ProjectCardEvent
<$> o .: "action"
<*> o .: "project_card"
<*> o .: "repository"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON ProjectColumnEvent where
parseJSON = withObject "ProjectColumnEvent" $ \o -> ProjectColumnEvent
<$> o .: "action"
<*> o .: "project_column"
<*> o .: "repository"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON ProjectEvent where
parseJSON = withObject "ProjectEvent" $ \o -> ProjectEvent
<$> o .: "action"
<*> o .: "project"
<*> o .: "repository"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON PublicEvent where
parseJSON = withObject "PublicEvent" $ \o -> PublicEvent
<$> o .: "repository"
<*> o .: "sender"
instance FromJSON PullRequestEvent where
parseJSON = withObject "PullRequestEvent" $ \o -> PullRequestEvent
<$> o .: "action"
<*> o .: "number"
<*> o .: "pull_request"
<*> o .: "repository"
<*> o .: "sender"
<*> (o .:? "installation" >>= maybe (pure Nothing) (.:? "id"))
instance FromJSON PullRequestReviewEvent where
parseJSON = withObject "PullRequestReviewEvent" $ \o -> PullRequestReviewEvent
<$> o .: "action"
<*> o .: "review"
<*> o .: "pull_request"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON PullRequestReviewCommentEvent where
parseJSON = withObject "PullRequestReviewCommentEvent" $ \o -> PullRequestReviewCommentEvent
<$> o .: "action"
<*> o .: "comment"
<*> o .: "pull_request"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON PushEvent where
parseJSON = withObject "PushEvent" $ \o -> PushEvent
<$> o .: "ref"
<*> o .:? "after"
<*> o .:? "before"
<*> o .: "created"
<*> o .: "deleted"
<*> o .: "forced"
<*> o .:? "base_ref"
<*> o .: "compare"
<*> o .:? "commits"
<*> o .:? "head_commit"
<*> o .: "repository"
<*> o .:? "organization"
<*> o .: "sender"
instance FromJSON ReleaseEvent where
parseJSON = withObject "ReleaseEvent" $ \o -> ReleaseEvent
<$> o .: "action"
<*> o .: "release"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON RepositoryEvent where
parseJSON = withObject "RepositoryEvent" $ \o -> RepositoryEvent
<$> o .: "action"
<*> o .: "repository"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON StatusEvent where
parseJSON = withObject "StatusEvent" $ \o -> StatusEvent
<$> o .: "id"
<*> o .: "sha"
<*> o .: "name"
<*> o .:? "target_url"
<*> o .: "context"
<*> o .:? "description"
<*> o .: "state"
<*> o .: "commit"
<*> o .: "created_at"
<*> o .: "updated_at"
<*> o .: "repository"
<*> o .: "sender"
instance FromJSON TeamEvent where
parseJSON = withObject "TeamEvent" $ \o -> TeamEvent
<$> o .: "action"
<*> o .: "team"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON TeamAddEvent where
parseJSON = withObject "TeamAddEvent" $ \o -> TeamAddEvent
<$> o .:? "team"
<*> o .: "repository"
<*> o .: "organization"
<*> o .: "sender"
instance FromJSON WatchEvent where
parseJSON = withObject "WatchEvent" $ \o -> WatchEvent
<$> o .: "action"
<*> o .: "repository"
<*> o .: "sender"