{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module Web.Slack.Conversation (
Conversation (..),
ConversationId (..),
ConversationType (..),
ChannelConversation (..),
GroupConversation (..),
ImConversation (..),
TeamId (..),
Purpose (..),
Topic (..),
ListReq (..),
mkListReq,
ListRsp (..),
HistoryReq (..),
mkHistoryReq,
HistoryRsp (..),
RepliesReq (..),
mkRepliesReq,
ResponseMetadata (..),
) where
import Data.Aeson
import Data.Aeson.Encoding
import Data.Aeson.KeyMap qualified as KM
import Data.Aeson.TH
import Data.Aeson.Types
import Data.Scientific
import Data.Text qualified as T
import Web.FormUrlEncoded
import Web.HttpApiData
import Web.Slack.Common
import Web.Slack.Pager.Types (PagedRequest (..), PagedResponse (..), ResponseMetadata (..))
import Web.Slack.Prelude
import Web.Slack.Util
data Topic = Topic
{ Topic -> Text
topicValue :: Text
, Topic -> Text
topicCreator :: Text
, Topic -> Integer
topicLastSet :: Integer
}
deriving stock (Topic -> Topic -> Bool
(Topic -> Topic -> Bool) -> (Topic -> Topic -> Bool) -> Eq Topic
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Topic -> Topic -> Bool
== :: Topic -> Topic -> Bool
$c/= :: Topic -> Topic -> Bool
/= :: Topic -> Topic -> Bool
Eq, Int -> Topic -> ShowS
[Topic] -> ShowS
Topic -> String
(Int -> Topic -> ShowS)
-> (Topic -> String) -> ([Topic] -> ShowS) -> Show Topic
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Topic -> ShowS
showsPrec :: Int -> Topic -> ShowS
$cshow :: Topic -> String
show :: Topic -> String
$cshowList :: [Topic] -> ShowS
showList :: [Topic] -> ShowS
Show, (forall x. Topic -> Rep Topic x)
-> (forall x. Rep Topic x -> Topic) -> Generic Topic
forall x. Rep Topic x -> Topic
forall x. Topic -> Rep Topic x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Topic -> Rep Topic x
from :: forall x. Topic -> Rep Topic x
$cto :: forall x. Rep Topic x -> Topic
to :: forall x. Rep Topic x -> Topic
Generic)
instance NFData Topic
$(deriveJSON (jsonOpts "topic") ''Topic)
data Purpose = Purpose
{ Purpose -> Text
purposeValue :: Text
, Purpose -> Text
purposeCreator :: Text
, Purpose -> Integer
purposeLastSet :: Integer
}
deriving stock (Purpose -> Purpose -> Bool
(Purpose -> Purpose -> Bool)
-> (Purpose -> Purpose -> Bool) -> Eq Purpose
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Purpose -> Purpose -> Bool
== :: Purpose -> Purpose -> Bool
$c/= :: Purpose -> Purpose -> Bool
/= :: Purpose -> Purpose -> Bool
Eq, Int -> Purpose -> ShowS
[Purpose] -> ShowS
Purpose -> String
(Int -> Purpose -> ShowS)
-> (Purpose -> String) -> ([Purpose] -> ShowS) -> Show Purpose
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Purpose -> ShowS
showsPrec :: Int -> Purpose -> ShowS
$cshow :: Purpose -> String
show :: Purpose -> String
$cshowList :: [Purpose] -> ShowS
showList :: [Purpose] -> ShowS
Show, (forall x. Purpose -> Rep Purpose x)
-> (forall x. Rep Purpose x -> Purpose) -> Generic Purpose
forall x. Rep Purpose x -> Purpose
forall x. Purpose -> Rep Purpose x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Purpose -> Rep Purpose x
from :: forall x. Purpose -> Rep Purpose x
$cto :: forall x. Rep Purpose x -> Purpose
to :: forall x. Rep Purpose x -> Purpose
Generic)
instance NFData Purpose
$(deriveJSON (jsonOpts "purpose") ''Purpose)
data ChannelConversation = ChannelConversation
{ ChannelConversation -> ConversationId
channelId :: ConversationId
, ChannelConversation -> Text
channelName :: Text
, ChannelConversation -> Integer
channelCreated :: Integer
, ChannelConversation -> Bool
channelIsArchived :: Bool
, ChannelConversation -> Bool
channelIsGeneral :: Bool
, ChannelConversation -> Integer
channelUnlinked :: Integer
, ChannelConversation -> Text
channelNameNormalized :: Text
, ChannelConversation -> Bool
channelIsShared :: Bool
,
ChannelConversation -> UserId
channelCreator :: UserId
, ChannelConversation -> Bool
channelIsExtShared :: Bool
, ChannelConversation -> Bool
channelIsOrgShared :: Bool
, ChannelConversation -> Maybe [TeamId]
channelSharedTeamIds :: Maybe [TeamId]
,
ChannelConversation -> Bool
channelIsPendingExtShared :: Bool
, ChannelConversation -> Maybe Bool
channelIsMember :: Maybe Bool
, ChannelConversation -> Topic
channelTopic :: Topic
, ChannelConversation -> Purpose
channelPurpose :: Purpose
, ChannelConversation -> [Text]
channelPreviousNames :: [Text]
, ChannelConversation -> Maybe Integer
channelNumMembers :: Maybe Integer
}
deriving stock (ChannelConversation -> ChannelConversation -> Bool
(ChannelConversation -> ChannelConversation -> Bool)
-> (ChannelConversation -> ChannelConversation -> Bool)
-> Eq ChannelConversation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChannelConversation -> ChannelConversation -> Bool
== :: ChannelConversation -> ChannelConversation -> Bool
$c/= :: ChannelConversation -> ChannelConversation -> Bool
/= :: ChannelConversation -> ChannelConversation -> Bool
Eq, Int -> ChannelConversation -> ShowS
[ChannelConversation] -> ShowS
ChannelConversation -> String
(Int -> ChannelConversation -> ShowS)
-> (ChannelConversation -> String)
-> ([ChannelConversation] -> ShowS)
-> Show ChannelConversation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChannelConversation -> ShowS
showsPrec :: Int -> ChannelConversation -> ShowS
$cshow :: ChannelConversation -> String
show :: ChannelConversation -> String
$cshowList :: [ChannelConversation] -> ShowS
showList :: [ChannelConversation] -> ShowS
Show, (forall x. ChannelConversation -> Rep ChannelConversation x)
-> (forall x. Rep ChannelConversation x -> ChannelConversation)
-> Generic ChannelConversation
forall x. Rep ChannelConversation x -> ChannelConversation
forall x. ChannelConversation -> Rep ChannelConversation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChannelConversation -> Rep ChannelConversation x
from :: forall x. ChannelConversation -> Rep ChannelConversation x
$cto :: forall x. Rep ChannelConversation x -> ChannelConversation
to :: forall x. Rep ChannelConversation x -> ChannelConversation
Generic)
instance NFData ChannelConversation
$(deriveJSON (jsonOpts "channel") ''ChannelConversation)
data GroupConversation = GroupConversation
{ GroupConversation -> ConversationId
groupId :: ConversationId
, GroupConversation -> Text
groupName :: Text
, GroupConversation -> Integer
groupCreated :: Integer
, GroupConversation -> Bool
groupIsArchived :: Bool
, GroupConversation -> Bool
groupIsGeneral :: Bool
, GroupConversation -> Integer
groupUnlinked :: Integer
, GroupConversation -> Text
groupNameNormalized :: Text
, GroupConversation -> Bool
groupIsShared :: Bool
,
GroupConversation -> UserId
groupCreator :: UserId
, GroupConversation -> Bool
groupIsExtShared :: Bool
, GroupConversation -> Bool
groupIsOrgShared :: Bool
, GroupConversation -> [TeamId]
groupSharedTeamIds :: [TeamId]
,
GroupConversation -> Bool
groupIsPendingExtShared :: Bool
, GroupConversation -> Bool
groupIsMember :: Bool
, GroupConversation -> Bool
groupIsPrivate :: Bool
, GroupConversation -> Bool
groupIsMpim :: Bool
, GroupConversation -> SlackTimestamp
groupLastRead :: SlackTimestamp
, GroupConversation -> Bool
groupIsOpen :: Bool
, GroupConversation -> Topic
groupTopic :: Topic
, GroupConversation -> Purpose
groupPurpose :: Purpose
, GroupConversation -> Scientific
groupPriority :: Scientific
}
deriving stock (GroupConversation -> GroupConversation -> Bool
(GroupConversation -> GroupConversation -> Bool)
-> (GroupConversation -> GroupConversation -> Bool)
-> Eq GroupConversation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GroupConversation -> GroupConversation -> Bool
== :: GroupConversation -> GroupConversation -> Bool
$c/= :: GroupConversation -> GroupConversation -> Bool
/= :: GroupConversation -> GroupConversation -> Bool
Eq, Int -> GroupConversation -> ShowS
[GroupConversation] -> ShowS
GroupConversation -> String
(Int -> GroupConversation -> ShowS)
-> (GroupConversation -> String)
-> ([GroupConversation] -> ShowS)
-> Show GroupConversation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GroupConversation -> ShowS
showsPrec :: Int -> GroupConversation -> ShowS
$cshow :: GroupConversation -> String
show :: GroupConversation -> String
$cshowList :: [GroupConversation] -> ShowS
showList :: [GroupConversation] -> ShowS
Show, (forall x. GroupConversation -> Rep GroupConversation x)
-> (forall x. Rep GroupConversation x -> GroupConversation)
-> Generic GroupConversation
forall x. Rep GroupConversation x -> GroupConversation
forall x. GroupConversation -> Rep GroupConversation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GroupConversation -> Rep GroupConversation x
from :: forall x. GroupConversation -> Rep GroupConversation x
$cto :: forall x. Rep GroupConversation x -> GroupConversation
to :: forall x. Rep GroupConversation x -> GroupConversation
Generic)
instance NFData GroupConversation
$(deriveJSON (jsonOpts "group") ''GroupConversation)
data ImConversation = ImConversation
{ ImConversation -> ConversationId
imId :: ConversationId
, ImConversation -> Integer
imCreated :: Integer
, ImConversation -> Bool
imIsArchived :: Bool
, ImConversation -> Bool
imIsOrgShared :: Bool
, ImConversation -> UserId
imUser :: UserId
, ImConversation -> Bool
imIsUserDeleted :: Bool
, ImConversation -> Scientific
imPriority :: Scientific
}
deriving stock (ImConversation -> ImConversation -> Bool
(ImConversation -> ImConversation -> Bool)
-> (ImConversation -> ImConversation -> Bool) -> Eq ImConversation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImConversation -> ImConversation -> Bool
== :: ImConversation -> ImConversation -> Bool
$c/= :: ImConversation -> ImConversation -> Bool
/= :: ImConversation -> ImConversation -> Bool
Eq, Int -> ImConversation -> ShowS
[ImConversation] -> ShowS
ImConversation -> String
(Int -> ImConversation -> ShowS)
-> (ImConversation -> String)
-> ([ImConversation] -> ShowS)
-> Show ImConversation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ImConversation -> ShowS
showsPrec :: Int -> ImConversation -> ShowS
$cshow :: ImConversation -> String
show :: ImConversation -> String
$cshowList :: [ImConversation] -> ShowS
showList :: [ImConversation] -> ShowS
Show, (forall x. ImConversation -> Rep ImConversation x)
-> (forall x. Rep ImConversation x -> ImConversation)
-> Generic ImConversation
forall x. Rep ImConversation x -> ImConversation
forall x. ImConversation -> Rep ImConversation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ImConversation -> Rep ImConversation x
from :: forall x. ImConversation -> Rep ImConversation x
$cto :: forall x. Rep ImConversation x -> ImConversation
to :: forall x. Rep ImConversation x -> ImConversation
Generic)
instance NFData ImConversation
$(deriveJSON (jsonOpts "im") ''ImConversation)
data Conversation
= Channel ChannelConversation
| Group GroupConversation
| Im ImConversation
deriving stock (Conversation -> Conversation -> Bool
(Conversation -> Conversation -> Bool)
-> (Conversation -> Conversation -> Bool) -> Eq Conversation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Conversation -> Conversation -> Bool
== :: Conversation -> Conversation -> Bool
$c/= :: Conversation -> Conversation -> Bool
/= :: Conversation -> Conversation -> Bool
Eq, Int -> Conversation -> ShowS
[Conversation] -> ShowS
Conversation -> String
(Int -> Conversation -> ShowS)
-> (Conversation -> String)
-> ([Conversation] -> ShowS)
-> Show Conversation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Conversation -> ShowS
showsPrec :: Int -> Conversation -> ShowS
$cshow :: Conversation -> String
show :: Conversation -> String
$cshowList :: [Conversation] -> ShowS
showList :: [Conversation] -> ShowS
Show, (forall x. Conversation -> Rep Conversation x)
-> (forall x. Rep Conversation x -> Conversation)
-> Generic Conversation
forall x. Rep Conversation x -> Conversation
forall x. Conversation -> Rep Conversation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Conversation -> Rep Conversation x
from :: forall x. Conversation -> Rep Conversation x
$cto :: forall x. Rep Conversation x -> Conversation
to :: forall x. Rep Conversation x -> Conversation
Generic)
instance NFData Conversation
instance FromJSON Conversation where
parseJSON :: Value -> Parser Conversation
parseJSON = String
-> (Object -> Parser Conversation) -> Value -> Parser Conversation
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Conversation" ((Object -> Parser Conversation) -> Value -> Parser Conversation)
-> (Object -> Parser Conversation) -> Value -> Parser Conversation
forall a b. (a -> b) -> a -> b
$ \Object
o ->
Parser Conversation
-> Maybe (Parser Conversation) -> Parser Conversation
forall a. a -> Maybe a -> a
fromMaybe (Object -> Parser Conversation
forall {a}. Object -> Parser a
noneMatched Object
o)
(Maybe (Parser Conversation) -> Parser Conversation)
-> Parser (Maybe (Parser Conversation)) -> Parser Conversation
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Key
-> (ChannelConversation -> Conversation)
-> Object
-> Parser (Maybe (Parser Conversation))
forall a b.
FromJSON a =>
Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen Key
"is_channel" ChannelConversation -> Conversation
Channel Object
o
Parser (Maybe (Parser Conversation))
-> Parser (Maybe (Parser Conversation))
-> Parser (Maybe (Parser Conversation))
forall (m :: * -> *) (a :: * -> *) b.
(Monad m, Alternative a) =>
m (a b) -> m (a b) -> m (a b)
`parseOr` Key
-> (GroupConversation -> Conversation)
-> Object
-> Parser (Maybe (Parser Conversation))
forall a b.
FromJSON a =>
Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen Key
"is_group" GroupConversation -> Conversation
Group Object
o
Parser (Maybe (Parser Conversation))
-> Parser (Maybe (Parser Conversation))
-> Parser (Maybe (Parser Conversation))
forall (m :: * -> *) (a :: * -> *) b.
(Monad m, Alternative a) =>
m (a b) -> m (a b) -> m (a b)
`parseOr` Key
-> (ImConversation -> Conversation)
-> Object
-> Parser (Maybe (Parser Conversation))
forall a b.
FromJSON a =>
Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen Key
"is_im" ImConversation -> Conversation
Im Object
o
where
noneMatched :: Object -> Parser a
noneMatched Object
o =
String -> Parser a -> Parser a
forall a. String -> Parser a -> Parser a
prependFailure
String
"parsing a Conversation failed: neither channel, group, nor im: "
(String -> Value -> Parser a
forall a. String -> Value -> Parser a
typeMismatch String
"Conversation" (Object -> Value
Object Object
o))
parseOr :: (Monad m, Alternative a) => m (a b) -> m (a b) -> m (a b)
parseOr :: forall (m :: * -> *) (a :: * -> *) b.
(Monad m, Alternative a) =>
m (a b) -> m (a b) -> m (a b)
parseOr = (a b -> a b -> a b) -> m (a b) -> m (a b) -> m (a b)
forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 a b -> a b -> a b
forall a. a a -> a a -> a a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
(<|>)
parseWhen :: (FromJSON a) => Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen :: forall a b.
FromJSON a =>
Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen Key
key a -> b
con Object
o = do
Bool
is <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
key Parser (Maybe Bool) -> Bool -> Parser Bool
forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
if Bool
is
then Maybe (Parser b) -> Parser (Maybe (Parser b))
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Parser b) -> Parser (Maybe (Parser b)))
-> (Parser b -> Maybe (Parser b))
-> Parser b
-> Parser (Maybe (Parser b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Parser b -> Maybe (Parser b)
forall a. a -> Maybe a
Just (Parser b -> Parser (Maybe (Parser b)))
-> Parser b -> Parser (Maybe (Parser b))
forall a b. (a -> b) -> a -> b
$ a -> b
con (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
else Maybe (Parser b) -> Parser (Maybe (Parser b))
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe (Parser b) -> Parser (Maybe (Parser b)))
-> Maybe (Parser b) -> Parser (Maybe (Parser b))
forall a b. (a -> b) -> a -> b
$ Maybe (Parser b)
forall a. Maybe a
Nothing
instance ToJSON Conversation where
toJSON :: Conversation -> Value
toJSON (Channel ChannelConversation
channel) =
let (Object Object
obj) = ChannelConversation -> Value
forall a. ToJSON a => a -> Value
toJSON ChannelConversation
channel
in Object -> Value
Object
(Object -> Value) -> (Object -> Object) -> Object -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_channel" (Bool -> Value
Bool Bool
True)
(Object -> Object) -> (Object -> Object) -> Object -> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_group" (Bool -> Value
Bool Bool
False)
(Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_im" (Bool -> Value
Bool Bool
False) Object
obj
toJSON (Group GroupConversation
theGroup) =
let (Object Object
obj) = GroupConversation -> Value
forall a. ToJSON a => a -> Value
toJSON GroupConversation
theGroup
in Object -> Value
Object
(Object -> Value) -> (Object -> Object) -> Object -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_channel" (Bool -> Value
Bool Bool
False)
(Object -> Object) -> (Object -> Object) -> Object -> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_group" (Bool -> Value
Bool Bool
True)
(Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_im" (Bool -> Value
Bool Bool
False) Object
obj
toJSON (Im ImConversation
im) =
let (Object Object
obj) = ImConversation -> Value
forall a. ToJSON a => a -> Value
toJSON ImConversation
im
in Object -> Value
Object
(Object -> Value) -> (Object -> Object) -> Object -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_channel" (Bool -> Value
Bool Bool
False)
(Object -> Object) -> (Object -> Object) -> Object -> Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_group" (Bool -> Value
Bool Bool
False)
(Object -> Value) -> Object -> Value
forall a b. (a -> b) -> a -> b
$ Key -> Value -> Object -> Object
forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_im" (Bool -> Value
Bool Bool
True) Object
obj
data ConversationType
= PublicChannelType
| PrivateChannelType
| MpimType
| ImType
deriving stock (ConversationType -> ConversationType -> Bool
(ConversationType -> ConversationType -> Bool)
-> (ConversationType -> ConversationType -> Bool)
-> Eq ConversationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ConversationType -> ConversationType -> Bool
== :: ConversationType -> ConversationType -> Bool
$c/= :: ConversationType -> ConversationType -> Bool
/= :: ConversationType -> ConversationType -> Bool
Eq, Int -> ConversationType -> ShowS
[ConversationType] -> ShowS
ConversationType -> String
(Int -> ConversationType -> ShowS)
-> (ConversationType -> String)
-> ([ConversationType] -> ShowS)
-> Show ConversationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConversationType -> ShowS
showsPrec :: Int -> ConversationType -> ShowS
$cshow :: ConversationType -> String
show :: ConversationType -> String
$cshowList :: [ConversationType] -> ShowS
showList :: [ConversationType] -> ShowS
Show, (forall x. ConversationType -> Rep ConversationType x)
-> (forall x. Rep ConversationType x -> ConversationType)
-> Generic ConversationType
forall x. Rep ConversationType x -> ConversationType
forall x. ConversationType -> Rep ConversationType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConversationType -> Rep ConversationType x
from :: forall x. ConversationType -> Rep ConversationType x
$cto :: forall x. Rep ConversationType x -> ConversationType
to :: forall x. Rep ConversationType x -> ConversationType
Generic)
instance NFData ConversationType
instance ToHttpApiData ConversationType where
toUrlPiece :: ConversationType -> Text
toUrlPiece ConversationType
PublicChannelType = Text
"public_channel"
toUrlPiece ConversationType
PrivateChannelType = Text
"private_channel"
toUrlPiece ConversationType
MpimType = Text
"mpim"
toUrlPiece ConversationType
ImType = Text
"im"
instance ToJSON ConversationType where
toJSON :: ConversationType -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value)
-> (ConversationType -> Text) -> ConversationType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ConversationType -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece
toEncoding :: ConversationType -> Encoding
toEncoding = Text -> Encoding
forall a. Text -> Encoding' a
text (Text -> Encoding)
-> (ConversationType -> Text) -> ConversationType -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ConversationType -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece
instance FromJSON ConversationType where
parseJSON :: Value -> Parser ConversationType
parseJSON = String
-> (Text -> Parser ConversationType)
-> Value
-> Parser ConversationType
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ConversationType" ((Text -> Parser ConversationType)
-> Value -> Parser ConversationType)
-> (Text -> Parser ConversationType)
-> Value
-> Parser ConversationType
forall a b. (a -> b) -> a -> b
$ \case
Text
"public_channel" -> ConversationType -> Parser ConversationType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
PublicChannelType
Text
"private_channel" -> ConversationType -> Parser ConversationType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
PrivateChannelType
Text
"mpim" -> ConversationType -> Parser ConversationType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
MpimType
Text
"im" -> ConversationType -> Parser ConversationType
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
ImType
Text
actual ->
String -> Parser ConversationType -> Parser ConversationType
forall a. String -> Parser a -> Parser a
prependFailure String
"must be either \"public_channel\", \"private_channel\", \"mpim\" or \"im\"!"
(Parser ConversationType -> Parser ConversationType)
-> (Value -> Parser ConversationType)
-> Value
-> Parser ConversationType
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> Value -> Parser ConversationType
forall a. String -> Value -> Parser a
typeMismatch String
"ConversationType"
(Value -> Parser ConversationType)
-> Value -> Parser ConversationType
forall a b. (a -> b) -> a -> b
$ Text -> Value
String Text
actual
data ListReq = ListReq
{ ListReq -> Maybe Bool
listReqExcludeArchived :: Maybe Bool
, ListReq -> [ConversationType]
listReqTypes :: [ConversationType]
, ListReq -> Maybe Cursor
listReqCursor :: Maybe Cursor
, ListReq -> Maybe Int
listReqLimit :: Maybe Int
, ListReq -> Maybe TeamId
listReqTeamId :: Maybe TeamId
}
deriving stock (ListReq -> ListReq -> Bool
(ListReq -> ListReq -> Bool)
-> (ListReq -> ListReq -> Bool) -> Eq ListReq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListReq -> ListReq -> Bool
== :: ListReq -> ListReq -> Bool
$c/= :: ListReq -> ListReq -> Bool
/= :: ListReq -> ListReq -> Bool
Eq, Int -> ListReq -> ShowS
[ListReq] -> ShowS
ListReq -> String
(Int -> ListReq -> ShowS)
-> (ListReq -> String) -> ([ListReq] -> ShowS) -> Show ListReq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListReq -> ShowS
showsPrec :: Int -> ListReq -> ShowS
$cshow :: ListReq -> String
show :: ListReq -> String
$cshowList :: [ListReq] -> ShowS
showList :: [ListReq] -> ShowS
Show, (forall x. ListReq -> Rep ListReq x)
-> (forall x. Rep ListReq x -> ListReq) -> Generic ListReq
forall x. Rep ListReq x -> ListReq
forall x. ListReq -> Rep ListReq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListReq -> Rep ListReq x
from :: forall x. ListReq -> Rep ListReq x
$cto :: forall x. Rep ListReq x -> ListReq
to :: forall x. Rep ListReq x -> ListReq
Generic)
instance NFData ListReq
$(deriveJSON (jsonOpts "listReq") ''ListReq)
mkListReq ::
ListReq
mkListReq :: ListReq
mkListReq =
ListReq
{ listReqExcludeArchived :: Maybe Bool
listReqExcludeArchived = Maybe Bool
forall a. Maybe a
Nothing
, listReqTypes :: [ConversationType]
listReqTypes = []
, listReqLimit :: Maybe Int
listReqLimit = Maybe Int
forall a. Maybe a
Nothing
, listReqTeamId :: Maybe TeamId
listReqTeamId = Maybe TeamId
forall a. Maybe a
Nothing
, listReqCursor :: Maybe Cursor
listReqCursor = Maybe Cursor
forall a. Maybe a
Nothing
}
instance ToForm ListReq where
toForm :: ListReq -> Form
toForm
( ListReq
{ Maybe Bool
listReqExcludeArchived :: ListReq -> Maybe Bool
listReqExcludeArchived :: Maybe Bool
listReqExcludeArchived
, listReqTypes :: ListReq -> [ConversationType]
listReqTypes = [ConversationType]
types
, Maybe TeamId
listReqTeamId :: ListReq -> Maybe TeamId
listReqTeamId :: Maybe TeamId
listReqTeamId
, Maybe Cursor
listReqCursor :: ListReq -> Maybe Cursor
listReqCursor :: Maybe Cursor
listReqCursor
, Maybe Int
listReqLimit :: ListReq -> Maybe Int
listReqLimit :: Maybe Int
listReqLimit
}
) =
Form
archivedForm
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Form
typesForm
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe TeamId -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"team_id" Maybe TeamId
listReqTeamId
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe Cursor -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"cursor" Maybe Cursor
listReqCursor
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe Int -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"limit" Maybe Int
listReqLimit
where
archivedForm :: Form
archivedForm =
Form -> (Bool -> Form) -> Maybe Bool -> Form
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Form
forall a. Monoid a => a
mempty (\Bool
val -> [(Text
"exclude_archived", Bool -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece Bool
val)]) Maybe Bool
listReqExcludeArchived
typesForm :: Form
typesForm =
if [ConversationType] -> Bool
forall mono. MonoFoldable mono => mono -> Bool
null [ConversationType]
types
then Form
forall a. Monoid a => a
mempty
else [(Text
"types", Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (ConversationType -> Text) -> [ConversationType] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map ConversationType -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece [ConversationType]
types)]
data ListRsp = ListRsp
{ ListRsp -> [Conversation]
listRspChannels :: [Conversation]
, ListRsp -> Maybe ResponseMetadata
listRspResponseMetadata :: Maybe ResponseMetadata
}
deriving stock (ListRsp -> ListRsp -> Bool
(ListRsp -> ListRsp -> Bool)
-> (ListRsp -> ListRsp -> Bool) -> Eq ListRsp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListRsp -> ListRsp -> Bool
== :: ListRsp -> ListRsp -> Bool
$c/= :: ListRsp -> ListRsp -> Bool
/= :: ListRsp -> ListRsp -> Bool
Eq, Int -> ListRsp -> ShowS
[ListRsp] -> ShowS
ListRsp -> String
(Int -> ListRsp -> ShowS)
-> (ListRsp -> String) -> ([ListRsp] -> ShowS) -> Show ListRsp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListRsp -> ShowS
showsPrec :: Int -> ListRsp -> ShowS
$cshow :: ListRsp -> String
show :: ListRsp -> String
$cshowList :: [ListRsp] -> ShowS
showList :: [ListRsp] -> ShowS
Show, (forall x. ListRsp -> Rep ListRsp x)
-> (forall x. Rep ListRsp x -> ListRsp) -> Generic ListRsp
forall x. Rep ListRsp x -> ListRsp
forall x. ListRsp -> Rep ListRsp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListRsp -> Rep ListRsp x
from :: forall x. ListRsp -> Rep ListRsp x
$cto :: forall x. Rep ListRsp x -> ListRsp
to :: forall x. Rep ListRsp x -> ListRsp
Generic)
instance NFData ListRsp
$(deriveFromJSON (jsonOpts "listRsp") ''ListRsp)
instance PagedRequest ListReq where
setCursor :: Maybe Cursor -> ListReq -> ListReq
setCursor Maybe Cursor
c ListReq
r = ListReq
r {listReqCursor = c}
instance PagedResponse ListRsp where
type ResponseObject ListRsp = Conversation
getResponseData :: ListRsp -> [ResponseObject ListRsp]
getResponseData ListRsp {[Conversation]
listRspChannels :: ListRsp -> [Conversation]
listRspChannels :: [Conversation]
listRspChannels} = [ResponseObject ListRsp]
[Conversation]
listRspChannels
getResponseMetadata :: ListRsp -> Maybe ResponseMetadata
getResponseMetadata ListRsp {Maybe ResponseMetadata
listRspResponseMetadata :: ListRsp -> Maybe ResponseMetadata
listRspResponseMetadata :: Maybe ResponseMetadata
listRspResponseMetadata} = Maybe ResponseMetadata
listRspResponseMetadata
data HistoryReq = HistoryReq
{ HistoryReq -> ConversationId
historyReqChannel :: ConversationId
, HistoryReq -> Maybe Cursor
historyReqCursor :: Maybe Cursor
, HistoryReq -> Int
historyReqCount :: Int
, HistoryReq -> Maybe SlackTimestamp
historyReqLatest :: Maybe SlackTimestamp
, HistoryReq -> Maybe SlackTimestamp
historyReqOldest :: Maybe SlackTimestamp
, HistoryReq -> Bool
historyReqInclusive :: Bool
}
deriving stock (HistoryReq -> HistoryReq -> Bool
(HistoryReq -> HistoryReq -> Bool)
-> (HistoryReq -> HistoryReq -> Bool) -> Eq HistoryReq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HistoryReq -> HistoryReq -> Bool
== :: HistoryReq -> HistoryReq -> Bool
$c/= :: HistoryReq -> HistoryReq -> Bool
/= :: HistoryReq -> HistoryReq -> Bool
Eq, Int -> HistoryReq -> ShowS
[HistoryReq] -> ShowS
HistoryReq -> String
(Int -> HistoryReq -> ShowS)
-> (HistoryReq -> String)
-> ([HistoryReq] -> ShowS)
-> Show HistoryReq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HistoryReq -> ShowS
showsPrec :: Int -> HistoryReq -> ShowS
$cshow :: HistoryReq -> String
show :: HistoryReq -> String
$cshowList :: [HistoryReq] -> ShowS
showList :: [HistoryReq] -> ShowS
Show, (forall x. HistoryReq -> Rep HistoryReq x)
-> (forall x. Rep HistoryReq x -> HistoryReq) -> Generic HistoryReq
forall x. Rep HistoryReq x -> HistoryReq
forall x. HistoryReq -> Rep HistoryReq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HistoryReq -> Rep HistoryReq x
from :: forall x. HistoryReq -> Rep HistoryReq x
$cto :: forall x. Rep HistoryReq x -> HistoryReq
to :: forall x. Rep HistoryReq x -> HistoryReq
Generic)
instance NFData HistoryReq
$(deriveJSON (jsonOpts "historyReq") ''HistoryReq)
mkHistoryReq ::
ConversationId ->
HistoryReq
mkHistoryReq :: ConversationId -> HistoryReq
mkHistoryReq ConversationId
channel =
HistoryReq
{ historyReqChannel :: ConversationId
historyReqChannel = ConversationId
channel
, historyReqCursor :: Maybe Cursor
historyReqCursor = Maybe Cursor
forall a. Maybe a
Nothing
, historyReqCount :: Int
historyReqCount = Int
100
, historyReqLatest :: Maybe SlackTimestamp
historyReqLatest = Maybe SlackTimestamp
forall a. Maybe a
Nothing
, historyReqOldest :: Maybe SlackTimestamp
historyReqOldest = Maybe SlackTimestamp
forall a. Maybe a
Nothing
, historyReqInclusive :: Bool
historyReqInclusive = Bool
True
}
instance ToForm HistoryReq where
toForm :: HistoryReq -> Form
toForm HistoryReq {Bool
Int
Maybe Cursor
Maybe SlackTimestamp
ConversationId
historyReqChannel :: HistoryReq -> ConversationId
historyReqCursor :: HistoryReq -> Maybe Cursor
historyReqCount :: HistoryReq -> Int
historyReqLatest :: HistoryReq -> Maybe SlackTimestamp
historyReqOldest :: HistoryReq -> Maybe SlackTimestamp
historyReqInclusive :: HistoryReq -> Bool
historyReqChannel :: ConversationId
historyReqCursor :: Maybe Cursor
historyReqCount :: Int
historyReqLatest :: Maybe SlackTimestamp
historyReqOldest :: Maybe SlackTimestamp
historyReqInclusive :: Bool
..} =
[(Text
"channel", ConversationId -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam ConversationId
historyReqChannel)]
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe Cursor -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"cursor" Maybe Cursor
historyReqCursor
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> [(Text
"count", Int -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Int
historyReqCount)]
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe SlackTimestamp -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"latest" Maybe SlackTimestamp
historyReqLatest
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe SlackTimestamp -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"oldest" Maybe SlackTimestamp
historyReqOldest
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> [(Text
"inclusive", Int -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (if Bool
historyReqInclusive then Int
1 :: Int else Int
0))]
data HistoryRsp = HistoryRsp
{ HistoryRsp -> [Message]
historyRspMessages :: [Message]
, HistoryRsp -> Maybe ResponseMetadata
historyRspResponseMetadata :: Maybe ResponseMetadata
}
deriving stock (HistoryRsp -> HistoryRsp -> Bool
(HistoryRsp -> HistoryRsp -> Bool)
-> (HistoryRsp -> HistoryRsp -> Bool) -> Eq HistoryRsp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HistoryRsp -> HistoryRsp -> Bool
== :: HistoryRsp -> HistoryRsp -> Bool
$c/= :: HistoryRsp -> HistoryRsp -> Bool
/= :: HistoryRsp -> HistoryRsp -> Bool
Eq, Int -> HistoryRsp -> ShowS
[HistoryRsp] -> ShowS
HistoryRsp -> String
(Int -> HistoryRsp -> ShowS)
-> (HistoryRsp -> String)
-> ([HistoryRsp] -> ShowS)
-> Show HistoryRsp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HistoryRsp -> ShowS
showsPrec :: Int -> HistoryRsp -> ShowS
$cshow :: HistoryRsp -> String
show :: HistoryRsp -> String
$cshowList :: [HistoryRsp] -> ShowS
showList :: [HistoryRsp] -> ShowS
Show, (forall x. HistoryRsp -> Rep HistoryRsp x)
-> (forall x. Rep HistoryRsp x -> HistoryRsp) -> Generic HistoryRsp
forall x. Rep HistoryRsp x -> HistoryRsp
forall x. HistoryRsp -> Rep HistoryRsp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HistoryRsp -> Rep HistoryRsp x
from :: forall x. HistoryRsp -> Rep HistoryRsp x
$cto :: forall x. Rep HistoryRsp x -> HistoryRsp
to :: forall x. Rep HistoryRsp x -> HistoryRsp
Generic)
instance NFData HistoryRsp
$(deriveJSON (jsonOpts "historyRsp") ''HistoryRsp)
instance PagedRequest HistoryReq where
setCursor :: Maybe Cursor -> HistoryReq -> HistoryReq
setCursor Maybe Cursor
c HistoryReq
r = HistoryReq
r {historyReqCursor = c}
instance PagedResponse HistoryRsp where
type ResponseObject HistoryRsp = Message
getResponseMetadata :: HistoryRsp -> Maybe ResponseMetadata
getResponseMetadata HistoryRsp {Maybe ResponseMetadata
historyRspResponseMetadata :: HistoryRsp -> Maybe ResponseMetadata
historyRspResponseMetadata :: Maybe ResponseMetadata
historyRspResponseMetadata} = Maybe ResponseMetadata
historyRspResponseMetadata
getResponseData :: HistoryRsp -> [ResponseObject HistoryRsp]
getResponseData HistoryRsp {[Message]
historyRspMessages :: HistoryRsp -> [Message]
historyRspMessages :: [Message]
historyRspMessages} = [ResponseObject HistoryRsp]
[Message]
historyRspMessages
data RepliesReq = RepliesReq
{ RepliesReq -> SlackTimestamp
repliesReqTs :: SlackTimestamp
, RepliesReq -> Maybe Cursor
repliesReqCursor :: Maybe Cursor
, RepliesReq -> ConversationId
repliesReqChannel :: ConversationId
, RepliesReq -> Int
repliesReqLimit :: Int
, RepliesReq -> Maybe SlackTimestamp
repliesReqLatest :: Maybe SlackTimestamp
, RepliesReq -> Maybe SlackTimestamp
repliesReqOldest :: Maybe SlackTimestamp
, RepliesReq -> Bool
repliesReqInclusive :: Bool
}
deriving stock (RepliesReq -> RepliesReq -> Bool
(RepliesReq -> RepliesReq -> Bool)
-> (RepliesReq -> RepliesReq -> Bool) -> Eq RepliesReq
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RepliesReq -> RepliesReq -> Bool
== :: RepliesReq -> RepliesReq -> Bool
$c/= :: RepliesReq -> RepliesReq -> Bool
/= :: RepliesReq -> RepliesReq -> Bool
Eq, Int -> RepliesReq -> ShowS
[RepliesReq] -> ShowS
RepliesReq -> String
(Int -> RepliesReq -> ShowS)
-> (RepliesReq -> String)
-> ([RepliesReq] -> ShowS)
-> Show RepliesReq
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RepliesReq -> ShowS
showsPrec :: Int -> RepliesReq -> ShowS
$cshow :: RepliesReq -> String
show :: RepliesReq -> String
$cshowList :: [RepliesReq] -> ShowS
showList :: [RepliesReq] -> ShowS
Show, (forall x. RepliesReq -> Rep RepliesReq x)
-> (forall x. Rep RepliesReq x -> RepliesReq) -> Generic RepliesReq
forall x. Rep RepliesReq x -> RepliesReq
forall x. RepliesReq -> Rep RepliesReq x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RepliesReq -> Rep RepliesReq x
from :: forall x. RepliesReq -> Rep RepliesReq x
$cto :: forall x. Rep RepliesReq x -> RepliesReq
to :: forall x. Rep RepliesReq x -> RepliesReq
Generic)
instance NFData RepliesReq
$(deriveJSON (jsonOpts "repliesReq") ''RepliesReq)
instance ToForm RepliesReq where
toForm :: RepliesReq -> Form
toForm RepliesReq {Bool
Int
Maybe Cursor
Maybe SlackTimestamp
SlackTimestamp
ConversationId
repliesReqTs :: RepliesReq -> SlackTimestamp
repliesReqCursor :: RepliesReq -> Maybe Cursor
repliesReqChannel :: RepliesReq -> ConversationId
repliesReqLimit :: RepliesReq -> Int
repliesReqLatest :: RepliesReq -> Maybe SlackTimestamp
repliesReqOldest :: RepliesReq -> Maybe SlackTimestamp
repliesReqInclusive :: RepliesReq -> Bool
repliesReqTs :: SlackTimestamp
repliesReqCursor :: Maybe Cursor
repliesReqChannel :: ConversationId
repliesReqLimit :: Int
repliesReqLatest :: Maybe SlackTimestamp
repliesReqOldest :: Maybe SlackTimestamp
repliesReqInclusive :: Bool
..} =
[(Text
"channel", ConversationId -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam ConversationId
repliesReqChannel)]
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> [(Text
"ts", SlackTimestamp -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam SlackTimestamp
repliesReqTs)]
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe Cursor -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"cursor" Maybe Cursor
repliesReqCursor
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> [(Text
"limit", Int -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam Int
repliesReqLimit)]
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe SlackTimestamp -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"latest" Maybe SlackTimestamp
repliesReqLatest
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe SlackTimestamp -> Form
forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"oldest" Maybe SlackTimestamp
repliesReqOldest
Form -> Form -> Form
forall a. Semigroup a => a -> a -> a
<> [(Text
"inclusive", Int -> Text
forall a. ToHttpApiData a => a -> Text
toQueryParam (if Bool
repliesReqInclusive then Int
1 :: Int else Int
0))]
instance PagedRequest RepliesReq where
setCursor :: Maybe Cursor -> RepliesReq -> RepliesReq
setCursor Maybe Cursor
c RepliesReq
r = RepliesReq
r {repliesReqCursor = c}
mkRepliesReq ::
ConversationId ->
SlackTimestamp ->
RepliesReq
mkRepliesReq :: ConversationId -> SlackTimestamp -> RepliesReq
mkRepliesReq ConversationId
channel SlackTimestamp
ts =
RepliesReq
{ repliesReqChannel :: ConversationId
repliesReqChannel = ConversationId
channel
, repliesReqCursor :: Maybe Cursor
repliesReqCursor = Maybe Cursor
forall a. Maybe a
Nothing
, repliesReqTs :: SlackTimestamp
repliesReqTs = SlackTimestamp
ts
, repliesReqLimit :: Int
repliesReqLimit = Int
100
, repliesReqLatest :: Maybe SlackTimestamp
repliesReqLatest = Maybe SlackTimestamp
forall a. Maybe a
Nothing
, repliesReqOldest :: Maybe SlackTimestamp
repliesReqOldest = Maybe SlackTimestamp
forall a. Maybe a
Nothing
, repliesReqInclusive :: Bool
repliesReqInclusive = Bool
True
}