{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TemplateHaskell #-}

-- FIXME(jadel): Use NoFieldSelectors when we drop everything before 9.2.

-- | Types for the [Slack Events API](https://api.slack.com/events).
module Web.Slack.Experimental.Events.Types where

import Data.Aeson
import Data.Aeson.TH
import Data.Time.Clock.System (SystemTime)
import Web.Slack.AesonUtils
import Web.Slack.Experimental.Blocks (SlackBlock)
import Web.Slack.Files.Types (FileObject)
import Web.Slack.Prelude
import Web.Slack.Types (ConversationId, TeamId, UserId)

-- | Not a ConversationType for some mysterious reason; this one has Channel as
-- an option, which does not exist as a ConversationType. Slack, why?
data ChannelType = Channel | Group | Im
  deriving stock (Int -> ChannelType -> ShowS
[ChannelType] -> ShowS
ChannelType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelType] -> ShowS
$cshowList :: [ChannelType] -> ShowS
show :: ChannelType -> String
$cshow :: ChannelType -> String
showsPrec :: Int -> ChannelType -> ShowS
$cshowsPrec :: Int -> ChannelType -> ShowS
Show, ChannelType -> ChannelType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChannelType -> ChannelType -> Bool
$c/= :: ChannelType -> ChannelType -> Bool
== :: ChannelType -> ChannelType -> Bool
$c== :: ChannelType -> ChannelType -> Bool
Eq)

$(deriveJSON snakeCaseOptions ''ChannelType)

-- | <https://api.slack.com/events/message>
-- and
-- <https://api.slack.com/events/message/file_share>
data MessageEvent = MessageEvent
  { MessageEvent -> Maybe [SlackBlock]
blocks :: Maybe [SlackBlock]
  , MessageEvent -> ConversationId
channel :: ConversationId
  , MessageEvent -> Text
text :: Text
  , MessageEvent -> ChannelType
channelType :: ChannelType
  , MessageEvent -> Maybe [FileObject]
files :: Maybe [FileObject]
  -- ^ @since 1.6.0.0
  , -- FIXME(jadel): clientMsgId??
    MessageEvent -> UserId
user :: UserId
  , MessageEvent -> Text
ts :: Text
  , MessageEvent -> Maybe Text
threadTs :: Maybe Text
  -- ^ Present if the message is in a thread
  , MessageEvent -> Maybe Text
appId :: Maybe Text
  -- ^ Present if it's sent by an app
  --
  --   For mysterious reasons, this is NOT
  --   <https://api.slack.com/events/message/bot_message>, this is a regular
  --   message but with bot metadata. I Think it's because there *is* an
  --   associated user.
  --
  --   See @botMessage.json@ golden parser test.
  , MessageEvent -> Maybe Text
botId :: Maybe Text
  -- ^ Present if it's sent by a bot user
  }
  deriving stock (Int -> MessageEvent -> ShowS
[MessageEvent] -> ShowS
MessageEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageEvent] -> ShowS
$cshowList :: [MessageEvent] -> ShowS
show :: MessageEvent -> String
$cshow :: MessageEvent -> String
showsPrec :: Int -> MessageEvent -> ShowS
$cshowsPrec :: Int -> MessageEvent -> ShowS
Show)

$(deriveFromJSON snakeCaseOptions ''MessageEvent)

-- | <https://api.slack.com/events/message/message_changed>
--
-- FIXME(jadel): implement. This is mega cursed! in the normal message event
-- the channel is called "channel" but here it is called "channelId" and also
-- has a "channel_name" and "channel_team". Why?!
--
-- We don't decode these on this basis.
data MessageUpdateEvent = MessageUpdateEvent
  { MessageUpdateEvent -> MessageEvent
message :: MessageEvent
  }
  deriving stock (Int -> MessageUpdateEvent -> ShowS
[MessageUpdateEvent] -> ShowS
MessageUpdateEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageUpdateEvent] -> ShowS
$cshowList :: [MessageUpdateEvent] -> ShowS
show :: MessageUpdateEvent -> String
$cshow :: MessageUpdateEvent -> String
showsPrec :: Int -> MessageUpdateEvent -> ShowS
$cshowsPrec :: Int -> MessageUpdateEvent -> ShowS
Show)

$(deriveFromJSON snakeCaseOptions ''MessageUpdateEvent)

-- | FIXME: this might be a Channel, but may also be missing some fields/have bonus
-- because Slack is cursed.
data CreatedChannel = CreatedChannel
  { CreatedChannel -> ConversationId
id :: ConversationId
  , CreatedChannel -> Bool
isChannel :: Bool
  , CreatedChannel -> Text
name :: Text
  , CreatedChannel -> Text
nameNormalized :: Text
  , CreatedChannel -> UserId
creator :: UserId
  , CreatedChannel -> SystemTime
created :: SystemTime
  , CreatedChannel -> Bool
isShared :: Bool
  , CreatedChannel -> Bool
isOrgShared :: Bool
  , -- what is this?
    CreatedChannel -> TeamId
contextTeamId :: TeamId
  }
  deriving stock (Int -> CreatedChannel -> ShowS
[CreatedChannel] -> ShowS
CreatedChannel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatedChannel] -> ShowS
$cshowList :: [CreatedChannel] -> ShowS
show :: CreatedChannel -> String
$cshow :: CreatedChannel -> String
showsPrec :: Int -> CreatedChannel -> ShowS
$cshowsPrec :: Int -> CreatedChannel -> ShowS
Show)

-- | A channel was created.
--
-- <https://api.slack.com/events/channel_created>
data ChannelCreatedEvent = ChannelCreatedEvent
  { ChannelCreatedEvent -> CreatedChannel
channel :: CreatedChannel
  }
  deriving stock (Int -> ChannelCreatedEvent -> ShowS
[ChannelCreatedEvent] -> ShowS
ChannelCreatedEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelCreatedEvent] -> ShowS
$cshowList :: [ChannelCreatedEvent] -> ShowS
show :: ChannelCreatedEvent -> String
$cshow :: ChannelCreatedEvent -> String
showsPrec :: Int -> ChannelCreatedEvent -> ShowS
$cshowsPrec :: Int -> ChannelCreatedEvent -> ShowS
Show)

$(deriveFromJSON snakeCaseOptions ''CreatedChannel)
$(deriveFromJSON snakeCaseOptions ''ChannelCreatedEvent)

-- | You left a channel.
--
-- <https://api.slack.com/events/channel_left>
data ChannelLeftEvent = ChannelLeftEvent
  { ChannelLeftEvent -> UserId
actorId :: UserId
  , ChannelLeftEvent -> ConversationId
channel :: ConversationId
  , ChannelLeftEvent -> Text
eventTs :: Text
  }
  deriving stock (Int -> ChannelLeftEvent -> ShowS
[ChannelLeftEvent] -> ShowS
ChannelLeftEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelLeftEvent] -> ShowS
$cshowList :: [ChannelLeftEvent] -> ShowS
show :: ChannelLeftEvent -> String
$cshow :: ChannelLeftEvent -> String
showsPrec :: Int -> ChannelLeftEvent -> ShowS
$cshowsPrec :: Int -> ChannelLeftEvent -> ShowS
Show)

$(deriveFromJSON snakeCaseOptions ''ChannelLeftEvent)

-- | <https://api.slack.com/events/url_verification>
data UrlVerificationPayload = UrlVerificationPayload
  { UrlVerificationPayload -> Text
challenge :: Text
  }
  deriving stock (Int -> UrlVerificationPayload -> ShowS
[UrlVerificationPayload] -> ShowS
UrlVerificationPayload -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UrlVerificationPayload] -> ShowS
$cshowList :: [UrlVerificationPayload] -> ShowS
show :: UrlVerificationPayload -> String
$cshow :: UrlVerificationPayload -> String
showsPrec :: Int -> UrlVerificationPayload -> ShowS
$cshowsPrec :: Int -> UrlVerificationPayload -> ShowS
Show)

$(deriveFromJSON snakeCaseOptions ''UrlVerificationPayload)

newtype EventId = EventId {EventId -> Text
unEventId :: Text}
  deriving newtype (Value -> Parser [EventId]
Value -> Parser EventId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [EventId]
$cparseJSONList :: Value -> Parser [EventId]
parseJSON :: Value -> Parser EventId
$cparseJSON :: Value -> Parser EventId
FromJSON)
  deriving stock (Int -> EventId -> ShowS
[EventId] -> ShowS
EventId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventId] -> ShowS
$cshowList :: [EventId] -> ShowS
show :: EventId -> String
$cshow :: EventId -> String
showsPrec :: Int -> EventId -> ShowS
$cshowsPrec :: Int -> EventId -> ShowS
Show)

newtype MessageId = MessageId {MessageId -> Text
unMessageId :: Text}
  deriving newtype (Value -> Parser [MessageId]
Value -> Parser MessageId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MessageId]
$cparseJSONList :: Value -> Parser [MessageId]
parseJSON :: Value -> Parser MessageId
$cparseJSON :: Value -> Parser MessageId
FromJSON)
  deriving stock (Int -> MessageId -> ShowS
[MessageId] -> ShowS
MessageId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageId] -> ShowS
$cshowList :: [MessageId] -> ShowS
show :: MessageId -> String
$cshow :: MessageId -> String
showsPrec :: Int -> MessageId -> ShowS
$cshowsPrec :: Int -> MessageId -> ShowS
Show, MessageId -> MessageId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageId -> MessageId -> Bool
$c/= :: MessageId -> MessageId -> Bool
== :: MessageId -> MessageId -> Bool
$c== :: MessageId -> MessageId -> Bool
Eq)

data Event
  = EventMessage MessageEvent
  | EventMessageChanged
  | -- | Weird message event of subtype channel_join. Sent "sometimes", according
    -- to a random Slack blog post from 2017:
    -- <https://api.slack.com/changelog/2017-05-rethinking-channel-entrance-and-exit-events-and-messages>
    --
    -- Documentation: <https://api.slack.com/events/message/channel_join>
    EventChannelJoinMessage
  | EventChannelCreated ChannelCreatedEvent
  | EventChannelLeft ChannelLeftEvent
  | EventUnknown Value
  deriving stock (Int -> Event -> ShowS
[Event] -> ShowS
Event -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Int -> Event -> ShowS
$cshowsPrec :: Int -> Event -> ShowS
Show, forall x. Rep Event x -> Event
forall x. Event -> Rep Event x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Event x -> Event
$cfrom :: forall x. Event -> Rep Event x
Generic)

instance FromJSON Event where
  parseJSON :: Value -> Parser Event
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"MessageEvent" \Object
obj -> do
    Text
tag :: Text <- Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
    Maybe Text
subtype :: Maybe Text <- Object
obj forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"subtype"
    case (Text
tag, Maybe Text
subtype) of
      (Text
"message", Maybe Text
Nothing) -> MessageEvent -> Event
EventMessage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON @MessageEvent (Object -> Value
Object Object
obj)
      (Text
"message", Just Text
"message_changed") -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Event
EventMessageChanged
      (Text
"message", Just Text
"channel_join") -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Event
EventChannelJoinMessage
      -- n.b. these are unified since it is *identical* to a Message event with
      -- a bonus files field
      (Text
"message", Just Text
"file_share") -> MessageEvent -> Event
EventMessage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON @MessageEvent (Object -> Value
Object Object
obj)
      (Text
"channel_created", Maybe Text
Nothing) -> ChannelCreatedEvent -> Event
EventChannelCreated forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
obj)
      (Text
"channel_left", Maybe Text
Nothing) -> ChannelLeftEvent -> Event
EventChannelLeft forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
obj)
      (Text, Maybe Text)
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Value -> Event
EventUnknown (Object -> Value
Object Object
obj)

data EventCallback = EventCallback
  { EventCallback -> EventId
eventId :: EventId
  , EventCallback -> TeamId
teamId :: TeamId
  , EventCallback -> SystemTime
eventTime :: SystemTime
  , EventCallback -> Event
event :: Event
  }
  deriving stock (Int -> EventCallback -> ShowS
[EventCallback] -> ShowS
EventCallback -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventCallback] -> ShowS
$cshowList :: [EventCallback] -> ShowS
show :: EventCallback -> String
$cshow :: EventCallback -> String
showsPrec :: Int -> EventCallback -> ShowS
$cshowsPrec :: Int -> EventCallback -> ShowS
Show)

$(deriveFromJSON snakeCaseOptions ''EventCallback)

data SlackWebhookEvent
  = EventUrlVerification UrlVerificationPayload
  | EventEventCallback EventCallback
  | EventUnknownWebhook Value
  deriving stock (Int -> SlackWebhookEvent -> ShowS
[SlackWebhookEvent] -> ShowS
SlackWebhookEvent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SlackWebhookEvent] -> ShowS
$cshowList :: [SlackWebhookEvent] -> ShowS
show :: SlackWebhookEvent -> String
$cshow :: SlackWebhookEvent -> String
showsPrec :: Int -> SlackWebhookEvent -> ShowS
$cshowsPrec :: Int -> SlackWebhookEvent -> ShowS
Show, forall x. Rep SlackWebhookEvent x -> SlackWebhookEvent
forall x. SlackWebhookEvent -> Rep SlackWebhookEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SlackWebhookEvent x -> SlackWebhookEvent
$cfrom :: forall x. SlackWebhookEvent -> Rep SlackWebhookEvent x
Generic)

instance FromJSON SlackWebhookEvent where
  parseJSON :: Value -> Parser SlackWebhookEvent
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SlackWebhookEvent" \Object
obj -> do
    Text
tag :: Text <- Object
obj forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
    case Text
tag of
      Text
"url_verification" -> UrlVerificationPayload -> SlackWebhookEvent
EventUrlVerification forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
obj)
      Text
"event_callback" -> EventCallback -> SlackWebhookEvent
EventEventCallback forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
obj)
      Text
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Value -> SlackWebhookEvent
EventUnknownWebhook (Object -> Value
Object Object
obj)

-- * Event responses

-- $eventResponses
--
-- By and large, Slack does not care about the response returned from event
-- handlers, at least for the 'EventEventCallback' as long as your service
-- 200s. The exception is 'EventUrlVerification', which is expected to return a
-- 'UrlVerificationResponse'

-- | Response for @url_verification@.
data UrlVerificationResponse = UrlVerificationResponse
  { UrlVerificationResponse -> Text
challenge :: Text
  }
  deriving stock (Int -> UrlVerificationResponse -> ShowS
[UrlVerificationResponse] -> ShowS
UrlVerificationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UrlVerificationResponse] -> ShowS
$cshowList :: [UrlVerificationResponse] -> ShowS
show :: UrlVerificationResponse -> String
$cshow :: UrlVerificationResponse -> String
showsPrec :: Int -> UrlVerificationResponse -> ShowS
$cshowsPrec :: Int -> UrlVerificationResponse -> ShowS
Show)

$(deriveToJSON defaultOptions ''UrlVerificationResponse)