{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Web.Slack
( SlackConfig (..),
mkSlackConfig,
apiTest,
authTest,
chatPostMessage,
chatUpdate,
conversationsList,
conversationsListAll,
conversationsHistory,
conversationsHistoryAll,
conversationsReplies,
repliesFetchAll,
getUserDesc,
usersList,
userLookupByEmail,
UsersConversations.usersConversations,
UsersConversations.usersConversationsAll,
authenticateReq,
Response,
LoadPage,
)
where
import Control.Arrow ((&&&))
import Data.Map qualified as Map
import Data.Maybe
import Data.Proxy (Proxy (..))
import Data.Text (Text)
import Network.HTTP.Client (Manager, newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.API hiding (addHeader)
import Servant.Client hiding (Response, baseUrl)
import Servant.Client.Core (AuthenticatedRequest)
import Web.Slack.Api qualified as Api
import Web.Slack.Auth qualified as Auth
import Web.Slack.Chat qualified as Chat
import Web.Slack.Common qualified as Common
import Web.Slack.Conversation qualified as Conversation
import Web.Slack.Internal
import Web.Slack.Pager
import Web.Slack.User qualified as User
import Web.Slack.UsersConversations qualified as UsersConversations
import Prelude
type Api =
"api.test"
:> ReqBody '[FormUrlEncoded] Api.TestReq
:> Post '[JSON] (ResponseJSON Api.TestRsp)
:<|> "auth.test"
:> AuthProtect "token"
:> Post '[JSON] (ResponseJSON Auth.TestRsp)
:<|> "conversations.list"
:> AuthProtect "token"
:> ReqBody '[FormUrlEncoded] Conversation.ListReq
:> Post '[JSON] (ResponseJSON Conversation.ListRsp)
:<|> "conversations.history"
:> AuthProtect "token"
:> ReqBody '[FormUrlEncoded] Conversation.HistoryReq
:> Post '[JSON] (ResponseJSON Conversation.HistoryRsp)
:<|> "conversations.replies"
:> AuthProtect "token"
:> ReqBody '[FormUrlEncoded] Conversation.RepliesReq
:> Post '[JSON] (ResponseJSON Conversation.HistoryRsp)
:<|> "chat.postMessage"
:> AuthProtect "token"
:> ReqBody '[FormUrlEncoded] Chat.PostMsgReq
:> Post '[JSON] (ResponseJSON Chat.PostMsgRsp)
:<|> "chat.update"
:> AuthProtect "token"
:> ReqBody '[FormUrlEncoded] Chat.UpdateReq
:> Post '[JSON] (ResponseJSON Chat.UpdateRsp)
:<|> "users.list"
:> AuthProtect "token"
:> Post '[JSON] (ResponseJSON User.ListRsp)
:<|> "users.lookupByEmail"
:> AuthProtect "token"
:> ReqBody '[FormUrlEncoded] User.Email
:> Post '[JSON] (ResponseJSON User.UserRsp)
apiTest ::
Manager ->
Api.TestReq ->
IO (Response Api.TestRsp)
apiTest :: Manager -> TestReq -> IO (Response TestRsp)
apiTest Manager
mgr TestReq
req = forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (TestReq -> ClientM (ResponseJSON TestRsp)
apiTest_ TestReq
req) Manager
mgr
apiTest_ ::
Api.TestReq ->
ClientM (ResponseJSON Api.TestRsp)
authTest ::
SlackConfig ->
IO (Response Auth.TestRsp)
authTest :: SlackConfig -> IO (Response TestRsp)
authTest = do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> ClientM (ResponseJSON TestRsp)
authTest_ AuthenticatedRequest (AuthProtect "token")
authR) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
authTest_ ::
AuthenticatedRequest (AuthProtect "token") ->
ClientM (ResponseJSON Auth.TestRsp)
conversationsList ::
SlackConfig ->
Conversation.ListReq ->
IO (Response Conversation.ListRsp)
conversationsList :: SlackConfig -> ListReq -> IO (Response ListRsp)
conversationsList = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ \ListReq
listReq -> do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> ListReq -> ClientM (ResponseJSON ListRsp)
conversationsList_ AuthenticatedRequest (AuthProtect "token")
authR ListReq
listReq) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
conversationsList_ ::
AuthenticatedRequest (AuthProtect "token") ->
Conversation.ListReq ->
ClientM (ResponseJSON Conversation.ListRsp)
conversationsListAll ::
SlackConfig ->
Conversation.ListReq ->
IO (LoadPage IO Conversation.Conversation)
conversationsListAll :: SlackConfig -> ListReq -> IO (LoadPage IO Conversation)
conversationsListAll = forall (m :: * -> *) req resp.
(MonadIO m, PagedRequest req, PagedResponse resp) =>
(req -> m (Response resp))
-> req -> m (LoadPage m (ResponseObject resp))
fetchAllBy forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> ListReq -> IO (Response ListRsp)
conversationsList
conversationsHistory ::
SlackConfig ->
Conversation.HistoryReq ->
IO (Response Conversation.HistoryRsp)
conversationsHistory :: SlackConfig -> HistoryReq -> IO (Response HistoryRsp)
conversationsHistory = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ \HistoryReq
histReq -> do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> HistoryReq -> ClientM (ResponseJSON HistoryRsp)
conversationsHistory_ AuthenticatedRequest (AuthProtect "token")
authR HistoryReq
histReq) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
conversationsHistory_ ::
AuthenticatedRequest (AuthProtect "token") ->
Conversation.HistoryReq ->
ClientM (ResponseJSON Conversation.HistoryRsp)
conversationsReplies ::
SlackConfig ->
Conversation.RepliesReq ->
IO (Response Conversation.HistoryRsp)
conversationsReplies :: SlackConfig -> RepliesReq -> IO (Response HistoryRsp)
conversationsReplies = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ \RepliesReq
repliesReq -> do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> RepliesReq -> ClientM (ResponseJSON HistoryRsp)
conversationsReplies_ AuthenticatedRequest (AuthProtect "token")
authR RepliesReq
repliesReq) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
conversationsReplies_ ::
AuthenticatedRequest (AuthProtect "token") ->
Conversation.RepliesReq ->
ClientM (ResponseJSON Conversation.HistoryRsp)
chatPostMessage ::
SlackConfig ->
Chat.PostMsgReq ->
IO (Response Chat.PostMsgRsp)
chatPostMessage :: SlackConfig -> PostMsgReq -> IO (Response PostMsgRsp)
chatPostMessage = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ \PostMsgReq
postReq -> do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> PostMsgReq -> ClientM (ResponseJSON PostMsgRsp)
chatPostMessage_ AuthenticatedRequest (AuthProtect "token")
authR PostMsgReq
postReq) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
chatPostMessage_ ::
AuthenticatedRequest (AuthProtect "token") ->
Chat.PostMsgReq ->
ClientM (ResponseJSON Chat.PostMsgRsp)
chatUpdate ::
SlackConfig ->
Chat.UpdateReq ->
IO (Response Chat.UpdateRsp)
chatUpdate :: SlackConfig -> UpdateReq -> IO (Response UpdateRsp)
chatUpdate = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ \UpdateReq
updateReq -> do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> UpdateReq -> ClientM (ResponseJSON UpdateRsp)
chatUpdate_ AuthenticatedRequest (AuthProtect "token")
authR UpdateReq
updateReq) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
chatUpdate_ ::
AuthenticatedRequest (AuthProtect "token") ->
Chat.UpdateReq ->
ClientM (ResponseJSON Chat.UpdateRsp)
usersList ::
SlackConfig ->
IO (Response User.ListRsp)
usersList :: SlackConfig -> IO (Response ListRsp)
usersList = do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> ClientM (ResponseJSON ListRsp)
usersList_ AuthenticatedRequest (AuthProtect "token")
authR) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
usersList_ ::
AuthenticatedRequest (AuthProtect "token") ->
ClientM (ResponseJSON User.ListRsp)
userLookupByEmail ::
SlackConfig ->
User.Email ->
IO (Response User.UserRsp)
userLookupByEmail :: SlackConfig -> Email -> IO (Response UserRsp)
userLookupByEmail = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> a -> b
$ \Email
email -> do
AuthenticatedRequest (AuthProtect "token")
authR <- SlackConfig -> AuthenticatedRequest (AuthProtect "token")
mkSlackAuthenticateReq
forall a. ClientM (ResponseJSON a) -> Manager -> IO (Response a)
run (AuthenticatedRequest (AuthProtect "token")
-> Email -> ClientM (ResponseJSON UserRsp)
userLookupByEmail_ AuthenticatedRequest (AuthProtect "token")
authR Email
email) forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> Manager
slackConfigManager
userLookupByEmail_ ::
AuthenticatedRequest (AuthProtect "token") ->
User.Email ->
ClientM (ResponseJSON User.UserRsp)
getUserDesc ::
(Common.UserId -> Text) ->
User.ListRsp ->
(Common.UserId -> Text)
getUserDesc :: (UserId -> Text) -> ListRsp -> UserId -> Text
getUserDesc UserId -> Text
unknownUserFn ListRsp
users =
let userMap :: Map UserId Text
userMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ (User -> UserId
User.userId forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& User -> Text
User.userName) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ListRsp -> [User]
User.listRspMembers ListRsp
users
in \UserId
userId -> forall a. a -> Maybe a -> a
fromMaybe (UserId -> Text
unknownUserFn UserId
userId) forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup UserId
userId Map UserId Text
userMap
conversationsHistoryAll ::
SlackConfig ->
Conversation.HistoryReq ->
IO (LoadPage IO Common.Message)
conversationsHistoryAll :: SlackConfig -> HistoryReq -> IO (LoadPage IO Message)
conversationsHistoryAll = forall (m :: * -> *) req resp.
(MonadIO m, PagedRequest req, PagedResponse resp) =>
(req -> m (Response resp))
-> req -> m (LoadPage m (ResponseObject resp))
fetchAllBy forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> HistoryReq -> IO (Response HistoryRsp)
conversationsHistory
repliesFetchAll ::
SlackConfig ->
Conversation.RepliesReq ->
IO (LoadPage IO Common.Message)
repliesFetchAll :: SlackConfig -> RepliesReq -> IO (LoadPage IO Message)
repliesFetchAll = forall (m :: * -> *) req resp.
(MonadIO m, PagedRequest req, PagedResponse resp) =>
(req -> m (Response resp))
-> req -> m (LoadPage m (ResponseObject resp))
fetchAllBy forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlackConfig -> RepliesReq -> IO (Response HistoryRsp)
conversationsReplies
TestReq -> ClientM (ResponseJSON TestRsp)
apiTest_
:<|> AuthenticatedRequest (AuthProtect "token")
-> ClientM (ResponseJSON TestRsp)
authTest_
:<|> AuthenticatedRequest (AuthProtect "token")
-> ListReq -> ClientM (ResponseJSON ListRsp)
conversationsList_
:<|> AuthenticatedRequest (AuthProtect "token")
-> HistoryReq -> ClientM (ResponseJSON HistoryRsp)
conversationsHistory_
:<|> AuthenticatedRequest (AuthProtect "token")
-> RepliesReq -> ClientM (ResponseJSON HistoryRsp)
conversationsReplies_
:<|> AuthenticatedRequest (AuthProtect "token")
-> PostMsgReq -> ClientM (ResponseJSON PostMsgRsp)
chatPostMessage_
:<|> AuthenticatedRequest (AuthProtect "token")
-> UpdateReq -> ClientM (ResponseJSON UpdateRsp)
chatUpdate_
:<|> AuthenticatedRequest (AuthProtect "token")
-> ClientM (ResponseJSON ListRsp)
usersList_
:<|> AuthenticatedRequest (AuthProtect "token")
-> Email -> ClientM (ResponseJSON UserRsp)
userLookupByEmail_ =
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy :: Proxy Api)
mkSlackConfig :: Text -> IO SlackConfig
mkSlackConfig :: Text -> IO SlackConfig
mkSlackConfig Text
token = Manager -> Text -> SlackConfig
SlackConfig forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ManagerSettings -> IO Manager
newManager ManagerSettings
tlsManagerSettings forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
token