{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.Connect.Webhooks
   ( Webhook(..)
   , WebhookEvent(..)
   ) where

import           Data.Aeson
import           Data.Aeson.Types
import           Data.Connect.AesonHelpers
import           Data.Connect.OrphanInstances ()
import qualified Data.Text                    as T
import           GHC.Generics

-- | When users of the host application perform updates your Atlassian Connect add-on will not be alerted /unless/
-- it listens to the 'WebhookEvent's coming from that application. Webhooks are the way to close the issue recency loop
-- in the Atlassian products. It is important to note that Webhooks are 'best effort' and that there is no guarantee
-- that the webhook will make it to your Atlassian Connect application.
--
-- The Atlassian connect webhook documentation explains this in more detail:
-- <https://developer.atlassian.com/static/connect/docs/modules/jira/webhook.html>
data Webhook = Webhook
   { Webhook -> WebhookEvent
webhookEvent :: WebhookEvent -- ^ The event that you want your Atlassian Connect add-on to watch.
   , Webhook -> Text
webhookUrl   :: T.Text -- ^ The relative URI that you wish to handle the webhook response.
   } deriving (Int -> Webhook -> ShowS
[Webhook] -> ShowS
Webhook -> String
(Int -> Webhook -> ShowS)
-> (Webhook -> String) -> ([Webhook] -> ShowS) -> Show Webhook
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Webhook] -> ShowS
$cshowList :: [Webhook] -> ShowS
show :: Webhook -> String
$cshow :: Webhook -> String
showsPrec :: Int -> Webhook -> ShowS
$cshowsPrec :: Int -> Webhook -> ShowS
Show, (forall x. Webhook -> Rep Webhook x)
-> (forall x. Rep Webhook x -> Webhook) -> Generic Webhook
forall x. Rep Webhook x -> Webhook
forall x. Webhook -> Rep Webhook x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Webhook x -> Webhook
$cfrom :: forall x. Webhook -> Rep Webhook x
Generic)

instance ToJSON Webhook where
   toJSON :: Webhook -> Value
toJSON = Options -> Webhook -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
baseOptions
      { fieldLabelModifier :: ShowS
fieldLabelModifier = String -> ShowS
stripFieldNamePrefix String
"webhook"
      }

-- | The webhook event that you wish to watch from your Atlassian Connect add-on.
data WebhookEvent
   = ConnectAddonDisabled
   | ConnectAddonEnabled
   | JiraWebhookPostFunction
   | JiraIssueCreated
   | JiraIssueDeleted
   | JiraIssueUpdated
   | JiraWorklogUpdated
   | JiraVersionCreated
   | JiraVersionDeleted
   | JiraVersionMerged
   | JiraVersionUpdated
   | JiraVersionMoved
   | JiraVersionReleased
   | JiraVersionUnreleased
   | JiraProjectCreated
   | JiraProjectUpdated
   | JiraProjectDeleted
   | JiraPluginEnabled
   | JiraPluginsUpgraded
   | JiraRemoteIssueLinkAggregateClearedEvent
   | JiraRemoteWorkflowPostFunction
   | JiraUserCreated
   | JiraUserDeleted
   | JiraUserUpdated
   | ConfluenceAttachmentCreated
   | ConfluenceAttachmentRemoved
   | ConfluenceAttachmentUpdated
   | ConfluenceAttachmentViewed
   | ConfluenceBlogCreated
   | ConfluenceBlogRemoved
   | ConfluenceBlogRestored
   | ConfluenceBlogTrashed
   | ConfluenceBlogUpdated
   | ConfluenceBlogViewed
   | ConfluenceCacheStatisticsChanged
   | ConfluenceCommentCreated
   | ConfluenceCommentRemoved
   | ConfluenceCommentUpdated
   | ConfluenceContentPermissionsUpdated
   | ConfluenceLabelAdded
   | ConfluenceLabelCreated
   | ConfluenceLabelDeleted
   | ConfluenceLabelRemoved
   | ConfluenceLogin
   | ConfluenceLoginFailed
   | ConfluenceLogout
   | ConfluencePageChildrenReordered
   | ConfluencePageCreated
   | ConfluencePageMoved
   | ConfluencePageRemoved
   | ConfluencePageRestored
   | ConfluencePageTrashed
   | ConfluencePageUpdated
   | ConfluencePageViewed
   | ConfluenceSearchPerformed
   | ConfluenceSpaceCreated
   | ConfluenceSpaceLogoUpdated
   | ConfluenceSpacePermissionsUpdated
   | ConfluenceSpaceRemoved
   | ConfluenceSpaceUpdated
   | ConfluenceStatusCleared
   | ConfluenceStatusCreated
   | ConfluenceStatusRemoved
   | ConfluenceUserCreated
   | ConfluenceUserDeactivated
   | ConfluenceUserFollowed
   | ConfluenceUserReactivated
   | ConfluenceUserRemoved
   | ConfluenceGroupCreated
   | ConfluenceGroupRemoved
   deriving (Int -> WebhookEvent -> ShowS
[WebhookEvent] -> ShowS
WebhookEvent -> String
(Int -> WebhookEvent -> ShowS)
-> (WebhookEvent -> String)
-> ([WebhookEvent] -> ShowS)
-> Show WebhookEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebhookEvent] -> ShowS
$cshowList :: [WebhookEvent] -> ShowS
show :: WebhookEvent -> String
$cshow :: WebhookEvent -> String
showsPrec :: Int -> WebhookEvent -> ShowS
$cshowsPrec :: Int -> WebhookEvent -> ShowS
Show)

instance ToJSON WebhookEvent where
   toJSON :: WebhookEvent -> Value
toJSON WebhookEvent
ConnectAddonDisabled = Text -> Value
String Text
"connect_addon_disabled"
   toJSON WebhookEvent
ConnectAddonEnabled = Text -> Value
String Text
"connect_addon_enabled"
   toJSON WebhookEvent
JiraWebhookPostFunction = Text -> Value
String Text
"jira-webhook-post-function"
   toJSON WebhookEvent
JiraIssueCreated = Text -> Value
String Text
"jira:issue_created"
   toJSON WebhookEvent
JiraIssueDeleted = Text -> Value
String Text
"jira:issue_deleted"
   toJSON WebhookEvent
JiraIssueUpdated = Text -> Value
String Text
"jira:issue_updated"
   toJSON WebhookEvent
JiraWorklogUpdated = Text -> Value
String Text
"jira:worklog_updated"
   toJSON WebhookEvent
JiraPluginEnabled = Text -> Value
String Text
"plugin_enabled"
   toJSON WebhookEvent
JiraPluginsUpgraded = Text -> Value
String Text
"plugins_upgraded"
   toJSON WebhookEvent
JiraVersionCreated = Text -> Value
String Text
"jira:version_created"
   toJSON WebhookEvent
JiraVersionDeleted = Text -> Value
String Text
"jira:version_deleted"
   toJSON WebhookEvent
JiraVersionMerged = Text -> Value
String Text
"jira:version_merged"
   toJSON WebhookEvent
JiraVersionUpdated = Text -> Value
String Text
"jira:version_updated"
   toJSON WebhookEvent
JiraVersionMoved = Text -> Value
String Text
"jira:version_moved"
   toJSON WebhookEvent
JiraVersionReleased = Text -> Value
String Text
"jira:version_released"
   toJSON WebhookEvent
JiraVersionUnreleased = Text -> Value
String Text
"jira:version_unreleased"
   toJSON WebhookEvent
JiraProjectCreated = Text -> Value
String Text
"jira:project_created"
   toJSON WebhookEvent
JiraProjectUpdated = Text -> Value
String Text
"jira:project_updated"
   toJSON WebhookEvent
JiraProjectDeleted = Text -> Value
String Text
"jira:project_deleted"
   toJSON WebhookEvent
JiraRemoteIssueLinkAggregateClearedEvent = Text -> Value
String Text
"remote_issue_link_aggregate_cleared_event"
   toJSON WebhookEvent
JiraRemoteWorkflowPostFunction = Text -> Value
String Text
"remote_workflow_post_function"
   toJSON WebhookEvent
JiraUserCreated = Text -> Value
String Text
"user_created"
   toJSON WebhookEvent
JiraUserDeleted = Text -> Value
String Text
"user_deleted"
   toJSON WebhookEvent
JiraUserUpdated = Text -> Value
String Text
"user_updated"
   toJSON WebhookEvent
ConfluenceAttachmentCreated = Value
"attachment_created"
   toJSON WebhookEvent
ConfluenceAttachmentRemoved = Value
"attachment_removed"
   toJSON WebhookEvent
ConfluenceAttachmentUpdated = Value
"attachment_updated"
   toJSON WebhookEvent
ConfluenceAttachmentViewed = Value
"attachment_viewed"
   toJSON WebhookEvent
ConfluenceBlogCreated = Value
"blog_created"
   toJSON WebhookEvent
ConfluenceBlogRemoved = Value
"blog_removed"
   toJSON WebhookEvent
ConfluenceBlogRestored = Value
"blog_restored"
   toJSON WebhookEvent
ConfluenceBlogTrashed = Value
"blog_trashed"
   toJSON WebhookEvent
ConfluenceBlogUpdated = Value
"blog_updated"
   toJSON WebhookEvent
ConfluenceBlogViewed = Value
"blog_viewed"
   toJSON WebhookEvent
ConfluenceCacheStatisticsChanged = Value
"cache_statistics_changed"
   toJSON WebhookEvent
ConfluenceCommentCreated = Value
"comment_created"
   toJSON WebhookEvent
ConfluenceCommentRemoved = Value
"comment_removed"
   toJSON WebhookEvent
ConfluenceCommentUpdated = Value
"comment_updated"
   toJSON WebhookEvent
ConfluenceContentPermissionsUpdated = Value
"content_permissions_updated"
   toJSON WebhookEvent
ConfluenceLabelAdded = Value
"label_added"
   toJSON WebhookEvent
ConfluenceLabelCreated = Value
"label_created"
   toJSON WebhookEvent
ConfluenceLabelDeleted = Value
"label_deleted"
   toJSON WebhookEvent
ConfluenceLabelRemoved = Value
"label_removed"
   toJSON WebhookEvent
ConfluenceLogin = Value
"login"
   toJSON WebhookEvent
ConfluenceLoginFailed = Value
"login_failed"
   toJSON WebhookEvent
ConfluenceLogout = Value
"logout"
   toJSON WebhookEvent
ConfluencePageChildrenReordered = Value
"page_children_reordered"
   toJSON WebhookEvent
ConfluencePageCreated = Value
"page_created"
   toJSON WebhookEvent
ConfluencePageMoved = Value
"page_moved"
   toJSON WebhookEvent
ConfluencePageRemoved = Value
"page_removed"
   toJSON WebhookEvent
ConfluencePageRestored = Value
"page_restored"
   toJSON WebhookEvent
ConfluencePageTrashed = Value
"page_trashed"
   toJSON WebhookEvent
ConfluencePageUpdated = Value
"page_updated"
   toJSON WebhookEvent
ConfluencePageViewed = Value
"page_viewed"
   toJSON WebhookEvent
ConfluenceSearchPerformed = Value
"search_performed"
   toJSON WebhookEvent
ConfluenceSpaceCreated = Value
"space_created"
   toJSON WebhookEvent
ConfluenceSpaceLogoUpdated = Value
"space_logo_updated"
   toJSON WebhookEvent
ConfluenceSpacePermissionsUpdated = Value
"space_permissions_updated"
   toJSON WebhookEvent
ConfluenceSpaceRemoved = Value
"space_removed"
   toJSON WebhookEvent
ConfluenceSpaceUpdated = Value
"space_updated"
   toJSON WebhookEvent
ConfluenceStatusCleared = Value
"status_cleared"
   toJSON WebhookEvent
ConfluenceStatusCreated = Value
"status_created"
   toJSON WebhookEvent
ConfluenceStatusRemoved = Value
"status_removed"
   toJSON WebhookEvent
ConfluenceUserCreated = Value
"user_created"
   toJSON WebhookEvent
ConfluenceUserDeactivated = Value
"user_deactivated"
   toJSON WebhookEvent
ConfluenceUserFollowed = Value
"user_followed"
   toJSON WebhookEvent
ConfluenceUserReactivated = Value
"user_reactivated"
   toJSON WebhookEvent
ConfluenceUserRemoved = Value
"user_removed"
   toJSON WebhookEvent
ConfluenceGroupCreated = Value
"group_created"
   toJSON WebhookEvent
ConfluenceGroupRemoved = Value
"group_removed"