{-# 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Topic -> Topic -> Bool
$c/= :: Topic -> Topic -> Bool
== :: Topic -> Topic -> Bool
$c== :: Topic -> Topic -> Bool
Eq, Int -> Topic -> ShowS
[Topic] -> ShowS
Topic -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Topic] -> ShowS
$cshowList :: [Topic] -> ShowS
show :: Topic -> String
$cshow :: Topic -> String
showsPrec :: Int -> Topic -> ShowS
$cshowsPrec :: Int -> Topic -> ShowS
Show, 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
$cto :: forall x. Rep Topic x -> Topic
$cfrom :: forall x. Topic -> Rep Topic x
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Purpose -> Purpose -> Bool
$c/= :: Purpose -> Purpose -> Bool
== :: Purpose -> Purpose -> Bool
$c== :: Purpose -> Purpose -> Bool
Eq, Int -> Purpose -> ShowS
[Purpose] -> ShowS
Purpose -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Purpose] -> ShowS
$cshowList :: [Purpose] -> ShowS
show :: Purpose -> String
$cshow :: Purpose -> String
showsPrec :: Int -> Purpose -> ShowS
$cshowsPrec :: Int -> Purpose -> ShowS
Show, 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
$cto :: forall x. Rep Purpose x -> Purpose
$cfrom :: forall x. Purpose -> Rep Purpose x
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChannelConversation -> ChannelConversation -> Bool
$c/= :: ChannelConversation -> ChannelConversation -> Bool
== :: ChannelConversation -> ChannelConversation -> Bool
$c== :: ChannelConversation -> ChannelConversation -> Bool
Eq, Int -> ChannelConversation -> ShowS
[ChannelConversation] -> ShowS
ChannelConversation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChannelConversation] -> ShowS
$cshowList :: [ChannelConversation] -> ShowS
show :: ChannelConversation -> String
$cshow :: ChannelConversation -> String
showsPrec :: Int -> ChannelConversation -> ShowS
$cshowsPrec :: Int -> ChannelConversation -> ShowS
Show, 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
$cto :: forall x. Rep ChannelConversation x -> ChannelConversation
$cfrom :: forall x. ChannelConversation -> Rep ChannelConversation x
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GroupConversation -> GroupConversation -> Bool
$c/= :: GroupConversation -> GroupConversation -> Bool
== :: GroupConversation -> GroupConversation -> Bool
$c== :: GroupConversation -> GroupConversation -> Bool
Eq, Int -> GroupConversation -> ShowS
[GroupConversation] -> ShowS
GroupConversation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GroupConversation] -> ShowS
$cshowList :: [GroupConversation] -> ShowS
show :: GroupConversation -> String
$cshow :: GroupConversation -> String
showsPrec :: Int -> GroupConversation -> ShowS
$cshowsPrec :: Int -> GroupConversation -> ShowS
Show, 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
$cto :: forall x. Rep GroupConversation x -> GroupConversation
$cfrom :: forall x. GroupConversation -> Rep GroupConversation x
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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImConversation -> ImConversation -> Bool
$c/= :: ImConversation -> ImConversation -> Bool
== :: ImConversation -> ImConversation -> Bool
$c== :: ImConversation -> ImConversation -> Bool
Eq, Int -> ImConversation -> ShowS
[ImConversation] -> ShowS
ImConversation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImConversation] -> ShowS
$cshowList :: [ImConversation] -> ShowS
show :: ImConversation -> String
$cshow :: ImConversation -> String
showsPrec :: Int -> ImConversation -> ShowS
$cshowsPrec :: Int -> ImConversation -> ShowS
Show, 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
$cto :: forall x. Rep ImConversation x -> ImConversation
$cfrom :: forall x. ImConversation -> Rep ImConversation x
Generic)
instance NFData ImConversation
$(deriveJSON (jsonOpts "im") ''ImConversation)
data Conversation
= Channel ChannelConversation
| Group GroupConversation
| Im ImConversation
deriving stock (Conversation -> Conversation -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Conversation -> Conversation -> Bool
$c/= :: Conversation -> Conversation -> Bool
== :: Conversation -> Conversation -> Bool
$c== :: Conversation -> Conversation -> Bool
Eq, Int -> Conversation -> ShowS
[Conversation] -> ShowS
Conversation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Conversation] -> ShowS
$cshowList :: [Conversation] -> ShowS
show :: Conversation -> String
$cshow :: Conversation -> String
showsPrec :: Int -> Conversation -> ShowS
$cshowsPrec :: Int -> Conversation -> ShowS
Show, 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
$cto :: forall x. Rep Conversation x -> Conversation
$cfrom :: forall x. Conversation -> Rep Conversation x
Generic)
instance NFData Conversation
instance FromJSON Conversation where
parseJSON :: Value -> Parser Conversation
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Conversation" forall a b. (a -> b) -> a -> b
$ \Object
o ->
forall a. a -> Maybe a -> a
fromMaybe (forall {a}. Object -> Parser a
noneMatched Object
o)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a b.
FromJSON a =>
Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen Key
"is_channel" ChannelConversation -> Conversation
Channel Object
o
forall (m :: * -> *) (a :: * -> *) b.
(Monad m, Alternative a) =>
m (a b) -> m (a b) -> m (a b)
`parseOr` forall a b.
FromJSON a =>
Key -> (a -> b) -> Object -> Parser (Maybe (Parser b))
parseWhen Key
"is_group" GroupConversation -> Conversation
Group Object
o
forall (m :: * -> *) (a :: * -> *) b.
(Monad m, Alternative a) =>
m (a b) -> m (a b) -> m (a b)
`parseOr` 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 =
forall a. String -> Parser a -> Parser a
prependFailure
String
"parsing a Conversation failed: neither channel, group, nor im: "
(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 = forall (m :: * -> *) a1 a2 r.
Monad m =>
(a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 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 forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
key forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
if Bool
is
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ a -> b
con forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
else forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Maybe a
Nothing
instance ToJSON Conversation where
toJSON :: Conversation -> Value
toJSON (Channel ChannelConversation
channel) =
let (Object Object
obj) = forall a. ToJSON a => a -> Value
toJSON ChannelConversation
channel
in Object -> Value
Object
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_channel" (Bool -> Value
Bool Bool
True)
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_group" (Bool -> Value
Bool Bool
False)
forall a b. (a -> b) -> a -> b
$ 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) = forall a. ToJSON a => a -> Value
toJSON GroupConversation
theGroup
in Object -> Value
Object
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_channel" (Bool -> Value
Bool Bool
False)
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_group" (Bool -> Value
Bool Bool
True)
forall a b. (a -> b) -> a -> b
$ 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) = forall a. ToJSON a => a -> Value
toJSON ImConversation
im
in Object -> Value
Object
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_channel" (Bool -> Value
Bool Bool
False)
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall v. Key -> v -> KeyMap v -> KeyMap v
KM.insert Key
"is_group" (Bool -> Value
Bool Bool
False)
forall a b. (a -> b) -> a -> b
$ 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConversationType -> ConversationType -> Bool
$c/= :: ConversationType -> ConversationType -> Bool
== :: ConversationType -> ConversationType -> Bool
$c== :: ConversationType -> ConversationType -> Bool
Eq, Int -> ConversationType -> ShowS
[ConversationType] -> ShowS
ConversationType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConversationType] -> ShowS
$cshowList :: [ConversationType] -> ShowS
show :: ConversationType -> String
$cshow :: ConversationType -> String
showsPrec :: Int -> ConversationType -> ShowS
$cshowsPrec :: Int -> ConversationType -> ShowS
Show, 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
$cto :: forall x. Rep ConversationType x -> ConversationType
$cfrom :: forall x. ConversationType -> Rep ConversationType x
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 = forall a. ToJSON a => a -> Value
toJSON forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. ToHttpApiData a => a -> Text
toUrlPiece
toEncoding :: ConversationType -> Encoding
toEncoding = forall a. Text -> Encoding' a
text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. ToHttpApiData a => a -> Text
toUrlPiece
instance FromJSON ConversationType where
parseJSON :: Value -> Parser ConversationType
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"ConversationType" forall a b. (a -> b) -> a -> b
$ \case
Text
"public_channel" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
PublicChannelType
Text
"private_channel" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
PrivateChannelType
Text
"mpim" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
MpimType
Text
"im" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ConversationType
ImType
Text
actual ->
forall a. String -> Parser a -> Parser a
prependFailure String
"must be either \"public_channel\", \"private_channel\", \"mpim\" or \"im\"!"
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. String -> Value -> Parser a
typeMismatch String
"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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListReq -> ListReq -> Bool
$c/= :: ListReq -> ListReq -> Bool
== :: ListReq -> ListReq -> Bool
$c== :: ListReq -> ListReq -> Bool
Eq, Int -> ListReq -> ShowS
[ListReq] -> ShowS
ListReq -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListReq] -> ShowS
$cshowList :: [ListReq] -> ShowS
show :: ListReq -> String
$cshow :: ListReq -> String
showsPrec :: Int -> ListReq -> ShowS
$cshowsPrec :: Int -> ListReq -> ShowS
Show, 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
$cto :: forall x. Rep ListReq x -> ListReq
$cfrom :: forall x. ListReq -> Rep ListReq x
Generic)
instance NFData ListReq
$(deriveJSON (jsonOpts "listReq") ''ListReq)
mkListReq ::
ListReq
mkListReq :: ListReq
mkListReq =
ListReq
{ listReqExcludeArchived :: Maybe Bool
listReqExcludeArchived = forall a. Maybe a
Nothing
, listReqTypes :: [ConversationType]
listReqTypes = []
, listReqLimit :: Maybe Int
listReqLimit = forall a. Maybe a
Nothing
, listReqTeamId :: Maybe TeamId
listReqTeamId = forall a. Maybe a
Nothing
, listReqCursor :: Maybe Cursor
listReqCursor = forall a. Maybe a
Nothing
}
instance ToForm ListReq where
toForm :: ListReq -> Form
toForm
( ListReq
{ Maybe Bool
listReqExcludeArchived :: Maybe Bool
listReqExcludeArchived :: ListReq -> Maybe Bool
listReqExcludeArchived
, listReqTypes :: ListReq -> [ConversationType]
listReqTypes = [ConversationType]
types
, Maybe TeamId
listReqTeamId :: Maybe TeamId
listReqTeamId :: ListReq -> Maybe TeamId
listReqTeamId
, Maybe Cursor
listReqCursor :: Maybe Cursor
listReqCursor :: ListReq -> Maybe Cursor
listReqCursor
, Maybe Int
listReqLimit :: Maybe Int
listReqLimit :: ListReq -> Maybe Int
listReqLimit
}
) =
Form
archivedForm
forall a. Semigroup a => a -> a -> a
<> Form
typesForm
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"team_id" Maybe TeamId
listReqTeamId
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"cursor" Maybe Cursor
listReqCursor
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"limit" Maybe Int
listReqLimit
where
archivedForm :: Form
archivedForm =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty (\Bool
val -> [(Text
"exclude_archived", forall a. ToHttpApiData a => a -> Text
toUrlPiece Bool
val)]) Maybe Bool
listReqExcludeArchived
typesForm :: Form
typesForm =
if forall mono. MonoFoldable mono => mono -> Bool
null [ConversationType]
types
then forall a. Monoid a => a
mempty
else [(Text
"types", Text -> [Text] -> Text
T.intercalate Text
"," forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListRsp -> ListRsp -> Bool
$c/= :: ListRsp -> ListRsp -> Bool
== :: ListRsp -> ListRsp -> Bool
$c== :: ListRsp -> ListRsp -> Bool
Eq, Int -> ListRsp -> ShowS
[ListRsp] -> ShowS
ListRsp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListRsp] -> ShowS
$cshowList :: [ListRsp] -> ShowS
show :: ListRsp -> String
$cshow :: ListRsp -> String
showsPrec :: Int -> ListRsp -> ShowS
$cshowsPrec :: Int -> ListRsp -> ShowS
Show, 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
$cto :: forall x. Rep ListRsp x -> ListRsp
$cfrom :: forall x. ListRsp -> Rep ListRsp x
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 :: Maybe Cursor
listReqCursor = Maybe Cursor
c}
instance PagedResponse ListRsp where
type ResponseObject ListRsp = Conversation
getResponseData :: ListRsp -> [ResponseObject ListRsp]
getResponseData ListRsp {[Conversation]
listRspChannels :: [Conversation]
listRspChannels :: ListRsp -> [Conversation]
listRspChannels} = [Conversation]
listRspChannels
getResponseMetadata :: ListRsp -> Maybe ResponseMetadata
getResponseMetadata ListRsp {Maybe ResponseMetadata
listRspResponseMetadata :: Maybe ResponseMetadata
listRspResponseMetadata :: ListRsp -> 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HistoryReq -> HistoryReq -> Bool
$c/= :: HistoryReq -> HistoryReq -> Bool
== :: HistoryReq -> HistoryReq -> Bool
$c== :: HistoryReq -> HistoryReq -> Bool
Eq, Int -> HistoryReq -> ShowS
[HistoryReq] -> ShowS
HistoryReq -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HistoryReq] -> ShowS
$cshowList :: [HistoryReq] -> ShowS
show :: HistoryReq -> String
$cshow :: HistoryReq -> String
showsPrec :: Int -> HistoryReq -> ShowS
$cshowsPrec :: Int -> HistoryReq -> ShowS
Show, 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
$cto :: forall x. Rep HistoryReq x -> HistoryReq
$cfrom :: forall x. HistoryReq -> Rep HistoryReq x
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 = forall a. Maybe a
Nothing
, historyReqCount :: Int
historyReqCount = Int
100
, historyReqLatest :: Maybe SlackTimestamp
historyReqLatest = forall a. Maybe a
Nothing
, historyReqOldest :: Maybe SlackTimestamp
historyReqOldest = 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
historyReqInclusive :: Bool
historyReqOldest :: Maybe SlackTimestamp
historyReqLatest :: Maybe SlackTimestamp
historyReqCount :: Int
historyReqCursor :: Maybe Cursor
historyReqChannel :: ConversationId
historyReqInclusive :: HistoryReq -> Bool
historyReqOldest :: HistoryReq -> Maybe SlackTimestamp
historyReqLatest :: HistoryReq -> Maybe SlackTimestamp
historyReqCount :: HistoryReq -> Int
historyReqCursor :: HistoryReq -> Maybe Cursor
historyReqChannel :: HistoryReq -> ConversationId
..} =
[(Text
"channel", forall a. ToHttpApiData a => a -> Text
toQueryParam ConversationId
historyReqChannel)]
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"cursor" Maybe Cursor
historyReqCursor
forall a. Semigroup a => a -> a -> a
<> [(Text
"count", forall a. ToHttpApiData a => a -> Text
toQueryParam Int
historyReqCount)]
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"latest" Maybe SlackTimestamp
historyReqLatest
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"oldest" Maybe SlackTimestamp
historyReqOldest
forall a. Semigroup a => a -> a -> a
<> [(Text
"inclusive", 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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HistoryRsp -> HistoryRsp -> Bool
$c/= :: HistoryRsp -> HistoryRsp -> Bool
== :: HistoryRsp -> HistoryRsp -> Bool
$c== :: HistoryRsp -> HistoryRsp -> Bool
Eq, Int -> HistoryRsp -> ShowS
[HistoryRsp] -> ShowS
HistoryRsp -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HistoryRsp] -> ShowS
$cshowList :: [HistoryRsp] -> ShowS
show :: HistoryRsp -> String
$cshow :: HistoryRsp -> String
showsPrec :: Int -> HistoryRsp -> ShowS
$cshowsPrec :: Int -> HistoryRsp -> ShowS
Show, 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
$cto :: forall x. Rep HistoryRsp x -> HistoryRsp
$cfrom :: forall x. HistoryRsp -> Rep HistoryRsp x
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 :: Maybe Cursor
historyReqCursor = Maybe Cursor
c}
instance PagedResponse HistoryRsp where
type ResponseObject HistoryRsp = Message
getResponseMetadata :: HistoryRsp -> Maybe ResponseMetadata
getResponseMetadata HistoryRsp {Maybe ResponseMetadata
historyRspResponseMetadata :: Maybe ResponseMetadata
historyRspResponseMetadata :: HistoryRsp -> Maybe ResponseMetadata
historyRspResponseMetadata} = Maybe ResponseMetadata
historyRspResponseMetadata
getResponseData :: HistoryRsp -> [ResponseObject HistoryRsp]
getResponseData HistoryRsp {[Message]
historyRspMessages :: [Message]
historyRspMessages :: HistoryRsp -> [Message]
historyRspMessages} = [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
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepliesReq -> RepliesReq -> Bool
$c/= :: RepliesReq -> RepliesReq -> Bool
== :: RepliesReq -> RepliesReq -> Bool
$c== :: RepliesReq -> RepliesReq -> Bool
Eq, Int -> RepliesReq -> ShowS
[RepliesReq] -> ShowS
RepliesReq -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RepliesReq] -> ShowS
$cshowList :: [RepliesReq] -> ShowS
show :: RepliesReq -> String
$cshow :: RepliesReq -> String
showsPrec :: Int -> RepliesReq -> ShowS
$cshowsPrec :: Int -> RepliesReq -> ShowS
Show, 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
$cto :: forall x. Rep RepliesReq x -> RepliesReq
$cfrom :: forall x. RepliesReq -> Rep RepliesReq x
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
repliesReqInclusive :: Bool
repliesReqOldest :: Maybe SlackTimestamp
repliesReqLatest :: Maybe SlackTimestamp
repliesReqLimit :: Int
repliesReqChannel :: ConversationId
repliesReqCursor :: Maybe Cursor
repliesReqTs :: SlackTimestamp
repliesReqInclusive :: RepliesReq -> Bool
repliesReqOldest :: RepliesReq -> Maybe SlackTimestamp
repliesReqLatest :: RepliesReq -> Maybe SlackTimestamp
repliesReqLimit :: RepliesReq -> Int
repliesReqChannel :: RepliesReq -> ConversationId
repliesReqCursor :: RepliesReq -> Maybe Cursor
repliesReqTs :: RepliesReq -> SlackTimestamp
..} =
[(Text
"channel", forall a. ToHttpApiData a => a -> Text
toQueryParam ConversationId
repliesReqChannel)]
forall a. Semigroup a => a -> a -> a
<> [(Text
"ts", forall a. ToHttpApiData a => a -> Text
toQueryParam SlackTimestamp
repliesReqTs)]
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"cursor" Maybe Cursor
repliesReqCursor
forall a. Semigroup a => a -> a -> a
<> [(Text
"limit", forall a. ToHttpApiData a => a -> Text
toQueryParam Int
repliesReqLimit)]
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"latest" Maybe SlackTimestamp
repliesReqLatest
forall a. Semigroup a => a -> a -> a
<> forall a. ToHttpApiData a => Text -> Maybe a -> Form
toQueryParamIfJust Text
"oldest" Maybe SlackTimestamp
repliesReqOldest
forall a. Semigroup a => a -> a -> a
<> [(Text
"inclusive", 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 :: Maybe Cursor
repliesReqCursor = Maybe Cursor
c}
mkRepliesReq ::
ConversationId ->
SlackTimestamp ->
RepliesReq
mkRepliesReq :: ConversationId -> SlackTimestamp -> RepliesReq
mkRepliesReq ConversationId
channel SlackTimestamp
ts =
RepliesReq
{ repliesReqChannel :: ConversationId
repliesReqChannel = ConversationId
channel
, repliesReqCursor :: Maybe Cursor
repliesReqCursor = forall a. Maybe a
Nothing
, repliesReqTs :: SlackTimestamp
repliesReqTs = SlackTimestamp
ts
, repliesReqLimit :: Int
repliesReqLimit = Int
100
, repliesReqLatest :: Maybe SlackTimestamp
repliesReqLatest = forall a. Maybe a
Nothing
, repliesReqOldest :: Maybe SlackTimestamp
repliesReqOldest = forall a. Maybe a
Nothing
, repliesReqInclusive :: Bool
repliesReqInclusive = Bool
True
}