{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TupleSections #-}

-- | This module contains the client-server API
-- https://matrix.org/docs/spec/client_server/r0.6.1
module Network.Matrix.Client
  ( -- * Client
    ClientSession,
    LoginCredentials (..),
    MatrixToken (..),
    Username (..),
    DeviceId (..),
    InitialDeviceDisplayName (..),
    LoginSecret (..),
    LoginResponse (..),
    getTokenFromEnv,
    createSession,
    login,
    loginToken,
    logout,

    -- * API
    MatrixM,
    MatrixIO,
    MatrixError (..),
    retry,
    retryWithLog,

    -- * User data
    UserID (..),
    getTokenOwner,

    -- * Room Events
    EventType (..),
    MRCreate (..),
    MRCanonicalAlias (..),
    MRGuestAccess (..),
    MRHistoryVisibility (..),
    MRName (..),
    MRTopic (..),
    PaginatedRoomMessages (..),
    StateKey (..),
    StateEvent (..),
    StateContent (..),
    getRoomEvent,
    getRoomMembers,
    getRoomState,
    getRoomStateEvent,
    getRoomMessages,
    redact,
    sendRoomStateEvent,

    -- * Room management
    RoomCreatePreset (..),
    RoomCreateRequest (..),
    createRoom,

    -- * Room participation
    ResolvedRoomAlias (..),
    TxnID (..),
    sendMessage,
    mkReply,
    module Network.Matrix.Events,
    setRoomAlias,
    setRoomVisibility,
    resolveRoomAlias,
    deleteRoomAlias,
    getRoomAliases,

    -- * Room membership
    RoomID (..),
    RoomAlias (..),
    banUser,
    checkRoomVisibility,
    forgetRoom,
    getJoinedRooms,
    getPublicRooms,
    getPublicRooms',
    inviteToRoom,
    joinRoom,
    joinRoomById,
    leaveRoomById,
    kickUser,
    knockOnRoom,
    unbanUser,

    -- * Filter
    EventFormat (..),
    EventFilter (..),
    defaultEventFilter,
    eventFilterAll,
    RoomEventFilter (..),
    defaultRoomEventFilter,
    roomEventFilterAll,
    StateFilter (..),
    defaultStateFilter,
    stateFilterAll,
    RoomFilter (..),
    defaultRoomFilter,
    Filter (..),
    defaultFilter,
    FilterID (..),
    messageFilter,
    createFilter,
    getFilter,

    -- * Account data

    AccountData(accountDataType),
    getAccountData,
    getAccountData',
    setAccountData,
    setAccountData',

    -- * Events
    sync,
    getTimelines,
    syncPoll,
    Author (..),
    Presence (..),
    RoomEvent (..),
    RoomSummary (..),
    TimelineSync (..),
    InvitedRoomSync (..),
    JoinedRoomSync (..),
    SyncResult (..),
    SyncResultRoom (..),
  )
where

import Control.Monad (mzero, void)
import Control.Monad.IO.Class (MonadIO(liftIO))
import Data.Aeson (FromJSON (..), ToJSON (..), Value (Object, String), encode, genericParseJSON, genericToJSON, object, withObject, withText, (.:), (.:?), (.=))
import qualified Data.Aeson as Aeson
import Data.Aeson.Casing (aesonPrefix, snakeCase)
import Data.Hashable (Hashable)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Map.Strict (Map, foldrWithKey)
import Data.Maybe (fromMaybe, catMaybes)
import Data.Proxy (Proxy(Proxy))
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8, encodeUtf8)
import GHC.Generics
import qualified Network.HTTP.Client as HTTP
import Network.HTTP.Types.URI (urlEncode)
import Network.Matrix.Events
import Network.Matrix.Internal
import Network.Matrix.Room
import qualified Network.URI as URI
import Data.Coerce
import Data.Bifunctor (bimap)
import Data.List (intersperse)
import Data.Aeson.Types (Parser)
import Control.Applicative
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL

-- $setup
-- >>> import Data.Aeson (decode)

data LoginCredentials = LoginCredentials
  { LoginCredentials -> Username
lUsername :: Username
  , LoginCredentials -> LoginSecret
lLoginSecret :: LoginSecret
  , LoginCredentials -> Text
lBaseUrl :: T.Text
  , LoginCredentials -> Maybe DeviceId
lDeviceId :: Maybe DeviceId
  , LoginCredentials -> Maybe InitialDeviceDisplayName
lInitialDeviceDisplayName :: Maybe InitialDeviceDisplayName
  }

mkLoginRequest :: LoginCredentials -> IO HTTP.Request
mkLoginRequest :: LoginCredentials -> IO Request
mkLoginRequest LoginCredentials {Maybe InitialDeviceDisplayName
Maybe DeviceId
Text
LoginSecret
Username
lInitialDeviceDisplayName :: Maybe InitialDeviceDisplayName
lDeviceId :: Maybe DeviceId
lBaseUrl :: Text
lLoginSecret :: LoginSecret
lUsername :: Username
lInitialDeviceDisplayName :: LoginCredentials -> Maybe InitialDeviceDisplayName
lDeviceId :: LoginCredentials -> Maybe DeviceId
lBaseUrl :: LoginCredentials -> Text
lLoginSecret :: LoginCredentials -> LoginSecret
lUsername :: LoginCredentials -> Username
..} =
  Text
-> Maybe DeviceId
-> Maybe InitialDeviceDisplayName
-> Username
-> LoginSecret
-> IO Request
mkLoginRequest' Text
lBaseUrl Maybe DeviceId
lDeviceId Maybe InitialDeviceDisplayName
lInitialDeviceDisplayName Username
lUsername LoginSecret
lLoginSecret

-- | 'login' allows you to generate a session token.
login :: LoginCredentials -> IO ClientSession
login :: LoginCredentials -> IO ClientSession
login = ((ClientSession, MatrixToken) -> ClientSession)
-> IO (ClientSession, MatrixToken) -> IO ClientSession
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (ClientSession, MatrixToken) -> ClientSession
forall a b. (a, b) -> a
fst (IO (ClientSession, MatrixToken) -> IO ClientSession)
-> (LoginCredentials -> IO (ClientSession, MatrixToken))
-> LoginCredentials
-> IO ClientSession
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LoginCredentials -> IO (ClientSession, MatrixToken)
loginToken 

-- | 'loginToken' allows you to generate a session token and recover the Matrix auth token.
loginToken :: LoginCredentials -> IO (ClientSession, MatrixToken)
loginToken :: LoginCredentials -> IO (ClientSession, MatrixToken)
loginToken LoginCredentials
cred = do
  Request
req <- LoginCredentials -> IO Request
mkLoginRequest LoginCredentials
cred
  Manager
manager <- IO Manager
mkManager
  Either MatrixError LoginResponse
resp' <- Manager -> Request -> IO (Either MatrixError LoginResponse)
forall a.
FromJSON a =>
Manager -> Request -> IO (Either MatrixError a)
doRequest' Manager
manager Request
req
  case Either MatrixError LoginResponse
resp' of
    Right LoginResponse {Text
lrDeviceId :: LoginResponse -> Text
lrHomeServer :: LoginResponse -> Text
lrAccessToken :: LoginResponse -> Text
lrUserId :: LoginResponse -> Text
lrDeviceId :: Text
lrHomeServer :: Text
lrAccessToken :: Text
lrUserId :: Text
..} -> (ClientSession, MatrixToken) -> IO (ClientSession, MatrixToken)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> MatrixToken -> Manager -> ClientSession
ClientSession (LoginCredentials -> Text
lBaseUrl LoginCredentials
cred) (Text -> MatrixToken
MatrixToken Text
lrAccessToken) Manager
manager, (Text -> MatrixToken
MatrixToken Text
lrAccessToken))
    Left MatrixError
err ->
      -- NOTE: There is nothing to recover after a failed login attempt
      String -> IO (ClientSession, MatrixToken)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> IO (ClientSession, MatrixToken))
-> String -> IO (ClientSession, MatrixToken)
forall a b. (a -> b) -> a -> b
$ MatrixError -> String
forall a. Show a => a -> String
show MatrixError
err

mkLogoutRequest :: ClientSession -> IO HTTP.Request
mkLogoutRequest :: ClientSession -> IO Request
mkLogoutRequest ClientSession {Text
Manager
MatrixToken
manager :: ClientSession -> Manager
token :: ClientSession -> MatrixToken
baseUrl :: ClientSession -> Text
manager :: Manager
token :: MatrixToken
baseUrl :: Text
..} = Text -> MatrixToken -> IO Request
mkLogoutRequest' Text
baseUrl MatrixToken
token

-- | 'logout' allows you to destroy a session token.
logout :: ClientSession -> MatrixIO ()
logout :: ClientSession -> MatrixIO ()
logout session :: ClientSession
session@ClientSession {Text
Manager
MatrixToken
manager :: Manager
token :: MatrixToken
baseUrl :: Text
manager :: ClientSession -> Manager
token :: ClientSession -> MatrixToken
baseUrl :: ClientSession -> Text
..} = do
  Request
req <- ClientSession -> IO Request
mkLogoutRequest ClientSession
session
  (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (() () -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$) (IO (Either MatrixError Value) -> MatrixIO ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$ Manager -> Request -> IO (Either MatrixError Value)
forall a.
FromJSON a =>
Manager -> Request -> IO (Either MatrixError a)
doRequest' @Value Manager
manager Request
req

-- | The session record, use 'createSession' to create it.
data ClientSession = ClientSession
  { ClientSession -> Text
baseUrl :: T.Text,
    ClientSession -> MatrixToken
token :: MatrixToken,
    ClientSession -> Manager
manager :: HTTP.Manager
  }

-- | 'createSession' creates the session record.
createSession ::
  -- | The matrix client-server base url, e.g. "https://matrix.org"
  T.Text ->
  -- | The user token
  MatrixToken ->
  IO ClientSession
createSession :: Text -> MatrixToken -> IO ClientSession
createSession Text
baseUrl' MatrixToken
token' = Text -> MatrixToken -> Manager -> ClientSession
ClientSession Text
baseUrl' MatrixToken
token' (Manager -> ClientSession) -> IO Manager -> IO ClientSession
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Manager
mkManager

mkRequest :: ClientSession -> Bool -> T.Text -> IO HTTP.Request
mkRequest :: ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession {Text
Manager
MatrixToken
manager :: Manager
token :: MatrixToken
baseUrl :: Text
manager :: ClientSession -> Manager
token :: ClientSession -> MatrixToken
baseUrl :: ClientSession -> Text
..} = Text -> MatrixToken -> Bool -> Text -> IO Request
mkRequest' Text
baseUrl MatrixToken
token

doRequest :: FromJSON a => ClientSession -> HTTP.Request -> MatrixIO a
doRequest :: ClientSession -> Request -> MatrixIO a
doRequest ClientSession {Text
Manager
MatrixToken
manager :: Manager
token :: MatrixToken
baseUrl :: Text
manager :: ClientSession -> Manager
token :: ClientSession -> MatrixToken
baseUrl :: ClientSession -> Text
..} = Manager -> Request -> MatrixIO a
forall a.
FromJSON a =>
Manager -> Request -> IO (Either MatrixError a)
doRequest' Manager
manager

-- | 'getTokenOwner' gets information about the owner of a given access token.
getTokenOwner :: ClientSession -> MatrixIO UserID
getTokenOwner :: ClientSession -> MatrixIO UserID
getTokenOwner ClientSession
session =
  ClientSession -> Request -> MatrixIO UserID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO UserID) -> IO Request -> MatrixIO UserID
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
"/_matrix/client/r0/account/whoami"

-- | A workaround data type to handle room create error being reported with a {message: "error"} response
data CreateRoomResponse = CreateRoomResponse
  { CreateRoomResponse -> Maybe Text
crrMessage :: Maybe T.Text,
    CreateRoomResponse -> Maybe Text
crrID :: Maybe T.Text
  }

instance FromJSON CreateRoomResponse where
  parseJSON :: Value -> Parser CreateRoomResponse
parseJSON (Object Object
o) = Maybe Text -> Maybe Text -> CreateRoomResponse
CreateRoomResponse (Maybe Text -> Maybe Text -> CreateRoomResponse)
-> Parser (Maybe Text) -> Parser (Maybe Text -> CreateRoomResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"message" Parser (Maybe Text -> CreateRoomResponse)
-> Parser (Maybe Text) -> Parser CreateRoomResponse
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"room_id"
  parseJSON Value
_ = Parser CreateRoomResponse
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-------------------------------------------------------------------------------
-- Room Event API Calls https://spec.matrix.org/v1.1/client-server-api/#getting-events-for-a-room

getRoomEvent :: ClientSession -> RoomID -> EventID -> MatrixIO RoomEvent
getRoomEvent :: ClientSession -> RoomID -> EventID -> MatrixIO RoomEvent
getRoomEvent ClientSession
session (RoomID Text
rid) (EventID Text
eid) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/event/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eid
  ClientSession -> Request -> MatrixIO RoomEvent
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session Request
request

data User = User { User -> Text
userDisplayName :: T.Text, User -> Maybe Text
userAvatarUrl :: Maybe T.Text }
  deriving Int -> User -> ShowS
[User] -> ShowS
User -> String
(Int -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show

instance FromJSON User where
  parseJSON :: Value -> Parser User
parseJSON = String -> (Object -> Parser User) -> Value -> Parser User
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"User" ((Object -> Parser User) -> Value -> Parser User)
-> (Object -> Parser User) -> Value -> Parser User
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Text
userDisplayName <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"display_name"
    Maybe Text
userAvatarUrl <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"avatar_url"
    User -> Parser User
forall (f :: * -> *) a. Applicative f => a -> f a
pure (User -> Parser User) -> User -> Parser User
forall a b. (a -> b) -> a -> b
$ User :: Text -> Maybe Text -> User
User {Maybe Text
Text
userAvatarUrl :: Maybe Text
userDisplayName :: Text
userAvatarUrl :: Maybe Text
userDisplayName :: Text
..}

-- | Unexported newtype to grant us a 'FromJSON' instance.
newtype JoinedUsers = JoinedUsers (Map UserID User)

instance FromJSON JoinedUsers where
  parseJSON :: Value -> Parser JoinedUsers
parseJSON = String
-> (Object -> Parser JoinedUsers) -> Value -> Parser JoinedUsers
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"JoinedUsers" ((Object -> Parser JoinedUsers) -> Value -> Parser JoinedUsers)
-> (Object -> Parser JoinedUsers) -> Value -> Parser JoinedUsers
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Map UserID User
users <- Object
o Object -> Key -> Parser (Map UserID User)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"joined"
    JoinedUsers -> Parser JoinedUsers
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JoinedUsers -> Parser JoinedUsers)
-> JoinedUsers -> Parser JoinedUsers
forall a b. (a -> b) -> a -> b
$ Map UserID User -> JoinedUsers
JoinedUsers Map UserID User
users

-- | This API returns a map of MXIDs to member info objects for
-- members of the room. The current user must be in the room for it to
-- work.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3roomsroomidjoined_members
getRoomMembers :: ClientSession -> RoomID -> MatrixIO (Map UserID User)
getRoomMembers :: ClientSession -> RoomID -> MatrixIO (Map UserID User)
getRoomMembers ClientSession
session (RoomID Text
rid) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/joined_members"
  (Either MatrixError JoinedUsers
 -> Either MatrixError (Map UserID User))
-> IO (Either MatrixError JoinedUsers)
-> MatrixIO (Map UserID User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((JoinedUsers -> Map UserID User)
-> Either MatrixError JoinedUsers
-> Either MatrixError (Map UserID User)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JoinedUsers -> Map UserID User
coerce) (IO (Either MatrixError JoinedUsers) -> MatrixIO (Map UserID User))
-> IO (Either MatrixError JoinedUsers)
-> MatrixIO (Map UserID User)
forall a b. (a -> b) -> a -> b
$ ClientSession -> Request -> IO (Either MatrixError JoinedUsers)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest @JoinedUsers ClientSession
session Request
request
    
newtype StateKey = StateKey T.Text
  deriving stock Int -> StateKey -> ShowS
[StateKey] -> ShowS
StateKey -> String
(Int -> StateKey -> ShowS)
-> (StateKey -> String) -> ([StateKey] -> ShowS) -> Show StateKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StateKey] -> ShowS
$cshowList :: [StateKey] -> ShowS
show :: StateKey -> String
$cshow :: StateKey -> String
showsPrec :: Int -> StateKey -> ShowS
$cshowsPrec :: Int -> StateKey -> ShowS
Show
  deriving newtype Value -> Parser [StateKey]
Value -> Parser StateKey
(Value -> Parser StateKey)
-> (Value -> Parser [StateKey]) -> FromJSON StateKey
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [StateKey]
$cparseJSONList :: Value -> Parser [StateKey]
parseJSON :: Value -> Parser StateKey
$cparseJSON :: Value -> Parser StateKey
FromJSON

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

data MRCreate = MRCreate { MRCreate -> UserID
mrcCreator :: UserID, MRCreate -> Integer
mrcRoomVersion :: Integer }
  deriving Int -> MRCreate -> ShowS
[MRCreate] -> ShowS
MRCreate -> String
(Int -> MRCreate -> ShowS)
-> (MRCreate -> String) -> ([MRCreate] -> ShowS) -> Show MRCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MRCreate] -> ShowS
$cshowList :: [MRCreate] -> ShowS
show :: MRCreate -> String
$cshow :: MRCreate -> String
showsPrec :: Int -> MRCreate -> ShowS
$cshowsPrec :: Int -> MRCreate -> ShowS
Show

instance FromJSON MRCreate where
  parseJSON :: Value -> Parser MRCreate
parseJSON = String -> (Object -> Parser MRCreate) -> Value -> Parser MRCreate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RoomCreate" ((Object -> Parser MRCreate) -> Value -> Parser MRCreate)
-> (Object -> Parser MRCreate) -> Value -> Parser MRCreate
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    UserID
mrcCreator <- Object
o Object -> Key -> Parser UserID
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"creator"
    Integer
mrcRoomVersion <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"room_version"
    MRCreate -> Parser MRCreate
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MRCreate -> Parser MRCreate) -> MRCreate -> Parser MRCreate
forall a b. (a -> b) -> a -> b
$ MRCreate :: UserID -> Integer -> MRCreate
MRCreate {Integer
UserID
mrcRoomVersion :: Integer
mrcCreator :: UserID
mrcRoomVersion :: Integer
mrcCreator :: UserID
..}

newtype MRName = MRName { MRName -> Text
mrnName :: T.Text }
  deriving Int -> MRName -> ShowS
[MRName] -> ShowS
MRName -> String
(Int -> MRName -> ShowS)
-> (MRName -> String) -> ([MRName] -> ShowS) -> Show MRName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MRName] -> ShowS
$cshowList :: [MRName] -> ShowS
show :: MRName -> String
$cshow :: MRName -> String
showsPrec :: Int -> MRName -> ShowS
$cshowsPrec :: Int -> MRName -> ShowS
Show

instance FromJSON MRName where
  parseJSON :: Value -> Parser MRName
parseJSON = String -> (Object -> Parser MRName) -> Value -> Parser MRName
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RoomName" ((Object -> Parser MRName) -> Value -> Parser MRName)
-> (Object -> Parser MRName) -> Value -> Parser MRName
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    Text -> MRName
MRName (Text -> MRName) -> Parser Text -> Parser MRName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name")

newtype MRCanonicalAlias = MRCanonicalAlias { MRCanonicalAlias -> Text
mrcAlias :: T.Text }
  deriving Int -> MRCanonicalAlias -> ShowS
[MRCanonicalAlias] -> ShowS
MRCanonicalAlias -> String
(Int -> MRCanonicalAlias -> ShowS)
-> (MRCanonicalAlias -> String)
-> ([MRCanonicalAlias] -> ShowS)
-> Show MRCanonicalAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MRCanonicalAlias] -> ShowS
$cshowList :: [MRCanonicalAlias] -> ShowS
show :: MRCanonicalAlias -> String
$cshow :: MRCanonicalAlias -> String
showsPrec :: Int -> MRCanonicalAlias -> ShowS
$cshowsPrec :: Int -> MRCanonicalAlias -> ShowS
Show

instance FromJSON MRCanonicalAlias where
  parseJSON :: Value -> Parser MRCanonicalAlias
parseJSON = String
-> (Object -> Parser MRCanonicalAlias)
-> Value
-> Parser MRCanonicalAlias
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RoomCanonicalAlias" ((Object -> Parser MRCanonicalAlias)
 -> Value -> Parser MRCanonicalAlias)
-> (Object -> Parser MRCanonicalAlias)
-> Value
-> Parser MRCanonicalAlias
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    Text -> MRCanonicalAlias
MRCanonicalAlias (Text -> MRCanonicalAlias)
-> Parser Text -> Parser MRCanonicalAlias
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"alias")

newtype MRGuestAccess = MRGuestAccess { MRGuestAccess -> Text
mrGuestAccess :: T.Text }
  deriving Int -> MRGuestAccess -> ShowS
[MRGuestAccess] -> ShowS
MRGuestAccess -> String
(Int -> MRGuestAccess -> ShowS)
-> (MRGuestAccess -> String)
-> ([MRGuestAccess] -> ShowS)
-> Show MRGuestAccess
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MRGuestAccess] -> ShowS
$cshowList :: [MRGuestAccess] -> ShowS
show :: MRGuestAccess -> String
$cshow :: MRGuestAccess -> String
showsPrec :: Int -> MRGuestAccess -> ShowS
$cshowsPrec :: Int -> MRGuestAccess -> ShowS
Show

instance FromJSON MRGuestAccess where
  parseJSON :: Value -> Parser MRGuestAccess
parseJSON = String
-> (Object -> Parser MRGuestAccess)
-> Value
-> Parser MRGuestAccess
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GuestAccess" ((Object -> Parser MRGuestAccess) -> Value -> Parser MRGuestAccess)
-> (Object -> Parser MRGuestAccess)
-> Value
-> Parser MRGuestAccess
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    Text -> MRGuestAccess
MRGuestAccess (Text -> MRGuestAccess) -> Parser Text -> Parser MRGuestAccess
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"guest_access")

newtype MRHistoryVisibility = MRHistoryVisibility { MRHistoryVisibility -> Text
mrHistoryVisibility :: T.Text }
  deriving Int -> MRHistoryVisibility -> ShowS
[MRHistoryVisibility] -> ShowS
MRHistoryVisibility -> String
(Int -> MRHistoryVisibility -> ShowS)
-> (MRHistoryVisibility -> String)
-> ([MRHistoryVisibility] -> ShowS)
-> Show MRHistoryVisibility
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MRHistoryVisibility] -> ShowS
$cshowList :: [MRHistoryVisibility] -> ShowS
show :: MRHistoryVisibility -> String
$cshow :: MRHistoryVisibility -> String
showsPrec :: Int -> MRHistoryVisibility -> ShowS
$cshowsPrec :: Int -> MRHistoryVisibility -> ShowS
Show

instance FromJSON MRHistoryVisibility where
  parseJSON :: Value -> Parser MRHistoryVisibility
parseJSON = String
-> (Object -> Parser MRHistoryVisibility)
-> Value
-> Parser MRHistoryVisibility
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"HistoryVisibility" ((Object -> Parser MRHistoryVisibility)
 -> Value -> Parser MRHistoryVisibility)
-> (Object -> Parser MRHistoryVisibility)
-> Value
-> Parser MRHistoryVisibility
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    Text -> MRHistoryVisibility
MRHistoryVisibility (Text -> MRHistoryVisibility)
-> Parser Text -> Parser MRHistoryVisibility
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"history_visibility")

newtype MRTopic = MRTopic { MRTopic -> Text
mrTopic :: T.Text }
  deriving Int -> MRTopic -> ShowS
[MRTopic] -> ShowS
MRTopic -> String
(Int -> MRTopic -> ShowS)
-> (MRTopic -> String) -> ([MRTopic] -> ShowS) -> Show MRTopic
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MRTopic] -> ShowS
$cshowList :: [MRTopic] -> ShowS
show :: MRTopic -> String
$cshow :: MRTopic -> String
showsPrec :: Int -> MRTopic -> ShowS
$cshowsPrec :: Int -> MRTopic -> ShowS
Show

instance FromJSON MRTopic where
  parseJSON :: Value -> Parser MRTopic
parseJSON = String -> (Object -> Parser MRTopic) -> Value -> Parser MRTopic
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RoomTopic" ((Object -> Parser MRTopic) -> Value -> Parser MRTopic)
-> (Object -> Parser MRTopic) -> Value -> Parser MRTopic
forall a b. (a -> b) -> a -> b
$ \Object
o ->
    Text -> MRTopic
MRTopic (Text -> MRTopic) -> Parser Text -> Parser MRTopic
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"topic")
    
data StateContent =
    StRoomCreate MRCreate
 -- | StRoomMember MRMember
 -- | StRoomPowerLevels MRPowerLevels
 -- | StRoomJoinRules MRJoinRules
  | StRoomCanonicalAlias MRCanonicalAlias
  | StRoomGuestAccess MRGuestAccess
  | StRoomHistoryVisibility MRHistoryVisibility
  | StRoomName MRName
  | StRoomTopic MRTopic
  | StOther Value
 --- | StSpaceParent MRSpaceParent
  deriving Int -> StateContent -> ShowS
[StateContent] -> ShowS
StateContent -> String
(Int -> StateContent -> ShowS)
-> (StateContent -> String)
-> ([StateContent] -> ShowS)
-> Show StateContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StateContent] -> ShowS
$cshowList :: [StateContent] -> ShowS
show :: StateContent -> String
$cshow :: StateContent -> String
showsPrec :: Int -> StateContent -> ShowS
$cshowsPrec :: Int -> StateContent -> ShowS
Show

pStRoomCreate :: Value -> Parser StateContent
pStRoomCreate :: Value -> Parser StateContent
pStRoomCreate Value
v = MRCreate -> StateContent
StRoomCreate (MRCreate -> StateContent)
-> Parser MRCreate -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MRCreate
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

pStRoomCanonicAlias :: Value -> Parser StateContent
pStRoomCanonicAlias :: Value -> Parser StateContent
pStRoomCanonicAlias Value
v = MRCanonicalAlias -> StateContent
StRoomCanonicalAlias (MRCanonicalAlias -> StateContent)
-> Parser MRCanonicalAlias -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MRCanonicalAlias
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

pStRoomGuestAccess :: Value -> Parser StateContent
pStRoomGuestAccess :: Value -> Parser StateContent
pStRoomGuestAccess Value
v = MRGuestAccess -> StateContent
StRoomGuestAccess (MRGuestAccess -> StateContent)
-> Parser MRGuestAccess -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MRGuestAccess
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

pStRoomHistoryVisibility :: Value -> Parser StateContent
pStRoomHistoryVisibility :: Value -> Parser StateContent
pStRoomHistoryVisibility Value
v = MRHistoryVisibility -> StateContent
StRoomHistoryVisibility (MRHistoryVisibility -> StateContent)
-> Parser MRHistoryVisibility -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MRHistoryVisibility
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

pStRoomName :: Value -> Parser StateContent
pStRoomName :: Value -> Parser StateContent
pStRoomName Value
v = MRName -> StateContent
StRoomName (MRName -> StateContent) -> Parser MRName -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MRName
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

pStRoomTopic :: Value -> Parser StateContent
pStRoomTopic :: Value -> Parser StateContent
pStRoomTopic Value
v = MRTopic -> StateContent
StRoomTopic (MRTopic -> StateContent) -> Parser MRTopic -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser MRTopic
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

pStRoomOther :: Value -> Parser StateContent
pStRoomOther :: Value -> Parser StateContent
pStRoomOther Value
v = Value -> StateContent
StOther (Value -> StateContent) -> Parser Value -> Parser StateContent
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Value
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
    
instance FromJSON StateContent where
  parseJSON :: Value -> Parser StateContent
parseJSON Value
v = 
        Value -> Parser StateContent
pStRoomCreate Value
v 
    Parser StateContent -> Parser StateContent -> Parser StateContent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser StateContent
pStRoomCanonicAlias Value
v
    Parser StateContent -> Parser StateContent -> Parser StateContent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser StateContent
pStRoomGuestAccess Value
v
    Parser StateContent -> Parser StateContent -> Parser StateContent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser StateContent
pStRoomHistoryVisibility Value
v
    Parser StateContent -> Parser StateContent -> Parser StateContent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser StateContent
pStRoomName Value
v
    Parser StateContent -> Parser StateContent -> Parser StateContent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser StateContent
pStRoomTopic Value
v
    Parser StateContent -> Parser StateContent -> Parser StateContent
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> Parser StateContent
pStRoomOther Value
v

-- TODO(SOLOMON): Should This constructor be in 'Event'?
data StateEvent = StateEvent
  { StateEvent -> StateContent
seContent :: StateContent
  , StateEvent -> EventID
seEventId :: EventID
  , StateEvent -> Integer
seOriginServerTimestamp :: Integer
  , StateEvent -> Maybe Value
sePreviousContent :: Maybe Value
  , StateEvent -> RoomID
seRoomId :: RoomID
  , StateEvent -> UserID
seSender :: UserID
  , StateEvent -> StateKey
seStateKey :: StateKey
  , StateEvent -> EventType
seEventType :: EventType
  , StateEvent -> Maybe Value
seUnsigned :: Maybe Value
  } deriving Int -> StateEvent -> ShowS
[StateEvent] -> ShowS
StateEvent -> String
(Int -> StateEvent -> ShowS)
-> (StateEvent -> String)
-> ([StateEvent] -> ShowS)
-> Show StateEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StateEvent] -> ShowS
$cshowList :: [StateEvent] -> ShowS
show :: StateEvent -> String
$cshow :: StateEvent -> String
showsPrec :: Int -> StateEvent -> ShowS
$cshowsPrec :: Int -> StateEvent -> ShowS
Show

instance FromJSON StateEvent where
  parseJSON :: Value -> Parser StateEvent
parseJSON = String
-> (Object -> Parser StateEvent) -> Value -> Parser StateEvent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"StateEvent" ((Object -> Parser StateEvent) -> Value -> Parser StateEvent)
-> (Object -> Parser StateEvent) -> Value -> Parser StateEvent
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    StateContent
seContent <- Object
o Object -> Key -> Parser StateContent
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content"
    EventID
seEventId <- (Text -> EventID) -> Parser Text -> Parser EventID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> EventID
EventID (Parser Text -> Parser EventID) -> Parser Text -> Parser EventID
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"event_id"
    Integer
seOriginServerTimestamp <- Object
o Object -> Key -> Parser Integer
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"origin_server_ts"
    Maybe Value
sePreviousContent <- Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"previous_content"
    RoomID
seRoomId <- (Text -> RoomID) -> Parser Text -> Parser RoomID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> RoomID
RoomID (Parser Text -> Parser RoomID) -> Parser Text -> Parser RoomID
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"room_id"
    UserID
seSender <- (Text -> UserID) -> Parser Text -> Parser UserID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> UserID
UserID (Parser Text -> Parser UserID) -> Parser Text -> Parser UserID
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"sender"
    StateKey
seStateKey <- Object
o Object -> Key -> Parser StateKey
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"state_key"
    EventType
seEventType <- Object
o Object -> Key -> Parser EventType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
    Maybe Value
seUnsigned <- Object
o Object -> Key -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"unsigned"
    StateEvent -> Parser StateEvent
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StateEvent -> Parser StateEvent)
-> StateEvent -> Parser StateEvent
forall a b. (a -> b) -> a -> b
$ StateEvent :: StateContent
-> EventID
-> Integer
-> Maybe Value
-> RoomID
-> UserID
-> StateKey
-> EventType
-> Maybe Value
-> StateEvent
StateEvent {Integer
Maybe Value
EventID
UserID
RoomID
StateContent
EventType
StateKey
seUnsigned :: Maybe Value
seEventType :: EventType
seStateKey :: StateKey
seSender :: UserID
seRoomId :: RoomID
sePreviousContent :: Maybe Value
seOriginServerTimestamp :: Integer
seEventId :: EventID
seContent :: StateContent
seUnsigned :: Maybe Value
seEventType :: EventType
seStateKey :: StateKey
seSender :: UserID
seRoomId :: RoomID
sePreviousContent :: Maybe Value
seOriginServerTimestamp :: Integer
seEventId :: EventID
seContent :: StateContent
..}
      
-- | Get the state events for the current state of a room.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3roomsroomidstate
getRoomState :: ClientSession -> RoomID -> MatrixIO [StateEvent]
getRoomState :: ClientSession -> RoomID -> MatrixIO [StateEvent]
getRoomState ClientSession
session (RoomID Text
rid) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/state"
  ClientSession -> Request -> MatrixIO [StateEvent]
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session Request
request

-- | Looks up the contents of a state event in a room. If the user is
-- joined to the room then the state is taken from the current state
-- of the room. If the user has left the room then the state is taken
-- from the state of the room when they left.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3roomsroomidstateeventtypestatekey
getRoomStateEvent :: ClientSession -> RoomID -> EventType -> StateKey -> MatrixIO StateEvent
getRoomStateEvent :: ClientSession
-> RoomID -> EventType -> StateKey -> MatrixIO StateEvent
getRoomStateEvent ClientSession
session (RoomID Text
rid) (EventType Text
et) (StateKey Text
key) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/state" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
et Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
key
  ClientSession -> Request -> MatrixIO StateEvent
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session Request
request

data Dir = F | B

renderDir :: Dir -> B.ByteString
renderDir :: Dir -> ByteString
renderDir Dir
F = ByteString
"f"
renderDir Dir
B = ByteString
"b"

data PaginatedRoomMessages = PaginatedRoomMessages
  { PaginatedRoomMessages -> [RoomEvent]
chunk :: [RoomEvent]
  , PaginatedRoomMessages -> Maybe Text
end :: Maybe T.Text
  -- ^ A token corresponding to the end of chunk. 
  , PaginatedRoomMessages -> Text
start :: T.Text
  -- ^ A token corresponding to the start of chunk.
  , PaginatedRoomMessages -> [StateEvent]
state :: [StateEvent]
  -- ^ A list of state events relevant to showing the chunk.
  } deriving Int -> PaginatedRoomMessages -> ShowS
[PaginatedRoomMessages] -> ShowS
PaginatedRoomMessages -> String
(Int -> PaginatedRoomMessages -> ShowS)
-> (PaginatedRoomMessages -> String)
-> ([PaginatedRoomMessages] -> ShowS)
-> Show PaginatedRoomMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaginatedRoomMessages] -> ShowS
$cshowList :: [PaginatedRoomMessages] -> ShowS
show :: PaginatedRoomMessages -> String
$cshow :: PaginatedRoomMessages -> String
showsPrec :: Int -> PaginatedRoomMessages -> ShowS
$cshowsPrec :: Int -> PaginatedRoomMessages -> ShowS
Show

instance FromJSON PaginatedRoomMessages where
  parseJSON :: Value -> Parser PaginatedRoomMessages
parseJSON = String
-> (Object -> Parser PaginatedRoomMessages)
-> Value
-> Parser PaginatedRoomMessages
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PaginatedRoomMessages" ((Object -> Parser PaginatedRoomMessages)
 -> Value -> Parser PaginatedRoomMessages)
-> (Object -> Parser PaginatedRoomMessages)
-> Value
-> Parser PaginatedRoomMessages
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    [RoomEvent]
chunk <- Object
o Object -> Key -> Parser [RoomEvent]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"chunk"
    Maybe Text
end <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"end"
    Text
start <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"start"
    [StateEvent]
state <- (Maybe [StateEvent] -> [StateEvent])
-> Parser (Maybe [StateEvent]) -> Parser [StateEvent]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([StateEvent] -> Maybe [StateEvent] -> [StateEvent]
forall a. a -> Maybe a -> a
fromMaybe []) (Parser (Maybe [StateEvent]) -> Parser [StateEvent])
-> Parser (Maybe [StateEvent]) -> Parser [StateEvent]
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser (Maybe [StateEvent])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"state"
    PaginatedRoomMessages -> Parser PaginatedRoomMessages
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PaginatedRoomMessages -> Parser PaginatedRoomMessages)
-> PaginatedRoomMessages -> Parser PaginatedRoomMessages
forall a b. (a -> b) -> a -> b
$ PaginatedRoomMessages :: [RoomEvent]
-> Maybe Text -> Text -> [StateEvent] -> PaginatedRoomMessages
PaginatedRoomMessages {[RoomEvent]
[StateEvent]
Maybe Text
Text
state :: [StateEvent]
start :: Text
end :: Maybe Text
chunk :: [RoomEvent]
state :: [StateEvent]
start :: Text
end :: Maybe Text
chunk :: [RoomEvent]
..}

getRoomMessages ::
  ClientSession ->
  -- | The room to get events from.
  RoomID ->
  -- | The direction to return events from.
  Dir ->
  -- | A 'RoomEventFilter' to filter returned events with.
  Maybe RoomEventFilter -> 
  -- | The Since value to start returning events from. 
  T.Text ->
  -- | The maximum number of events to return. Default: 10.
  Maybe Int ->
  -- | The token to stop returning events at. 
  Maybe Int ->
  MatrixIO PaginatedRoomMessages
getRoomMessages :: ClientSession
-> RoomID
-> Dir
-> Maybe RoomEventFilter
-> Text
-> Maybe Int
-> Maybe Int
-> MatrixIO PaginatedRoomMessages
getRoomMessages ClientSession
session (RoomID Text
rid) Dir
dir Maybe RoomEventFilter
roomFilter Text
fromToken Maybe Int
limit Maybe Int
toToken = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/messages"
  let dir' :: ByteString
dir' = ByteString
"dir=" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Dir -> ByteString
renderDir Dir
dir
      filter' :: Maybe ByteString
filter' = ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (RoomEventFilter -> ByteString) -> RoomEventFilter -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
mappend ByteString
"filter=" (ByteString -> ByteString)
-> (RoomEventFilter -> ByteString) -> RoomEventFilter -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RoomEventFilter -> ByteString
forall a. ToJSON a => a -> ByteString
encode (RoomEventFilter -> ByteString)
-> Maybe RoomEventFilter -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe RoomEventFilter
roomFilter
      from' :: ByteString
from' = Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
"from=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
fromToken
      limit' :: Maybe ByteString
limit' = ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (Int -> ByteString) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
mappend ByteString
"limit=" (ByteString -> ByteString)
-> (Int -> ByteString) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
forall a. ToJSON a => a -> ByteString
encode (Int -> ByteString) -> Maybe Int -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
limit
      to' :: Maybe ByteString
to' = ByteString -> ByteString
BL.toStrict (ByteString -> ByteString)
-> (Int -> ByteString) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
mappend ByteString
"from=" (ByteString -> ByteString)
-> (Int -> ByteString) -> Int -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ByteString
forall a. ToJSON a => a -> ByteString
encode (Int -> ByteString) -> Maybe Int -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
toToken
      queryString :: ByteString
queryString = ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
mappend ByteString
"?" (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> ByteString) -> [ByteString] -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
intersperse ByteString
"&" ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ [ByteString
dir', ByteString
from' ] [ByteString] -> [ByteString] -> [ByteString]
forall a. Semigroup a => a -> a -> a
<> [Maybe ByteString] -> [ByteString]
forall a. [Maybe a] -> [a]
catMaybes [Maybe ByteString
to', Maybe ByteString
limit', Maybe ByteString
filter']
  ClientSession -> Request -> MatrixIO PaginatedRoomMessages
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO PaginatedRoomMessages)
-> Request -> MatrixIO PaginatedRoomMessages
forall a b. (a -> b) -> a -> b
$ Request
request { queryString :: ByteString
HTTP.queryString = ByteString
queryString }

-- | Send arbitrary state events to a room. These events will be overwritten if
-- <room id>, <event type> and <state key> all match.
-- https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3roomsroomidstateeventtypestatekey
sendRoomStateEvent :: ClientSession -> RoomID -> EventType -> StateKey -> Value -> MatrixIO EventID 
sendRoomStateEvent :: ClientSession
-> RoomID -> EventType -> StateKey -> Value -> MatrixIO EventID
sendRoomStateEvent ClientSession
session (RoomID Text
rid) (EventType Text
et) (StateKey Text
key) Value
event = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeUriComponent Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/state/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeUriComponent Text
et Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeUriComponent Text
key
  ClientSession -> Request -> MatrixIO EventID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO EventID) -> Request -> MatrixIO EventID
forall a b. (a -> b) -> a -> b
$
    Request
request { method :: ByteString
HTTP.method = ByteString
"PUT"
            , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
event
            }

newtype TxnID = TxnID T.Text deriving (Int -> TxnID -> ShowS
[TxnID] -> ShowS
TxnID -> String
(Int -> TxnID -> ShowS)
-> (TxnID -> String) -> ([TxnID] -> ShowS) -> Show TxnID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxnID] -> ShowS
$cshowList :: [TxnID] -> ShowS
show :: TxnID -> String
$cshow :: TxnID -> String
showsPrec :: Int -> TxnID -> ShowS
$cshowsPrec :: Int -> TxnID -> ShowS
Show, TxnID -> TxnID -> Bool
(TxnID -> TxnID -> Bool) -> (TxnID -> TxnID -> Bool) -> Eq TxnID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxnID -> TxnID -> Bool
$c/= :: TxnID -> TxnID -> Bool
== :: TxnID -> TxnID -> Bool
$c== :: TxnID -> TxnID -> Bool
Eq)

-- | This endpoint is used to send a message event to a room.
-- https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3roomsroomidsendeventtypetxnid
sendMessage :: ClientSession -> RoomID -> Event -> TxnID -> MatrixIO EventID
sendMessage :: ClientSession -> RoomID -> Event -> TxnID -> MatrixIO EventID
sendMessage ClientSession
session (RoomID Text
roomId) Event
event (TxnID Text
txnId) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
path
  ClientSession -> Request -> MatrixIO EventID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest
    ClientSession
session
    ( Request
request
        { method :: ByteString
HTTP.method = ByteString
"PUT",
          requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Event -> ByteString
forall a. ToJSON a => a -> ByteString
encode Event
event
        }
    )
  where
    path :: Text
path = Text
"/_matrix/client/r0/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/send/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eventId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txnId
    eventId :: Text
eventId = Event -> Text
eventType Event
event

redact :: ClientSession -> RoomID -> EventID -> TxnID -> T.Text -> MatrixIO EventID
redact :: ClientSession
-> RoomID -> EventID -> TxnID -> Text -> MatrixIO EventID
redact ClientSession
session (RoomID Text
rid) (EventID Text
eid) (TxnID Text
txnid) Text
reason = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/redact/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
txnid
  let body :: Value
body = [Pair] -> Value
object [Key
"reason" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text -> Value
String Text
reason]
  ClientSession -> Request -> MatrixIO EventID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO EventID) -> Request -> MatrixIO EventID
forall a b. (a -> b) -> a -> b
$
    Request
request { method :: ByteString
HTTP.method = ByteString
"PUT"
            , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
            }

-------------------------------------------------------------------------------
-- Room API Calls https://spec.matrix.org/v1.1/client-server-api/#rooms-1

-- | Create a new room with various configuration options.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3createroom
createRoom :: ClientSession -> RoomCreateRequest -> MatrixIO RoomID
createRoom :: ClientSession -> RoomCreateRequest -> MatrixIO RoomID
createRoom ClientSession
session RoomCreateRequest
rcr = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
"/_matrix/client/v3/createRoom"
  Either MatrixError CreateRoomResponse -> Either MatrixError RoomID
toRoomID
    (Either MatrixError CreateRoomResponse
 -> Either MatrixError RoomID)
-> IO (Either MatrixError CreateRoomResponse) -> MatrixIO RoomID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ClientSession
-> Request -> IO (Either MatrixError CreateRoomResponse)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest
      ClientSession
session
      ( Request
request
          { method :: ByteString
HTTP.method = ByteString
"POST",
            requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ RoomCreateRequest -> ByteString
forall a. ToJSON a => a -> ByteString
encode RoomCreateRequest
rcr
          }
      )
  where
    toRoomID :: Either MatrixError CreateRoomResponse -> Either MatrixError RoomID
    toRoomID :: Either MatrixError CreateRoomResponse -> Either MatrixError RoomID
toRoomID Either MatrixError CreateRoomResponse
resp = case Either MatrixError CreateRoomResponse
resp of
      Left MatrixError
err -> MatrixError -> Either MatrixError RoomID
forall a b. a -> Either a b
Left MatrixError
err
      Right CreateRoomResponse
crr -> case (CreateRoomResponse -> Maybe Text
crrID CreateRoomResponse
crr, CreateRoomResponse -> Maybe Text
crrMessage CreateRoomResponse
crr) of
        (Just Text
roomID, Maybe Text
_) -> RoomID -> Either MatrixError RoomID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RoomID -> Either MatrixError RoomID)
-> RoomID -> Either MatrixError RoomID
forall a b. (a -> b) -> a -> b
$ Text -> RoomID
RoomID Text
roomID
        (Maybe Text
_, Just Text
message) -> MatrixError -> Either MatrixError RoomID
forall a b. a -> Either a b
Left (MatrixError -> Either MatrixError RoomID)
-> MatrixError -> Either MatrixError RoomID
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Int -> MatrixError
MatrixError Text
"UNKNOWN" Text
message Maybe Int
forall a. Maybe a
Nothing
        (Maybe Text, Maybe Text)
_ -> MatrixError -> Either MatrixError RoomID
forall a b. a -> Either a b
Left (MatrixError -> Either MatrixError RoomID)
-> MatrixError -> Either MatrixError RoomID
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Int -> MatrixError
MatrixError Text
"UNKOWN" Text
"" Maybe Int
forall a. Maybe a
Nothing

newtype RoomAlias = RoomAlias T.Text deriving (Int -> RoomAlias -> ShowS
[RoomAlias] -> ShowS
RoomAlias -> String
(Int -> RoomAlias -> ShowS)
-> (RoomAlias -> String)
-> ([RoomAlias] -> ShowS)
-> Show RoomAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoomAlias] -> ShowS
$cshowList :: [RoomAlias] -> ShowS
show :: RoomAlias -> String
$cshow :: RoomAlias -> String
showsPrec :: Int -> RoomAlias -> ShowS
$cshowsPrec :: Int -> RoomAlias -> ShowS
Show, RoomAlias -> RoomAlias -> Bool
(RoomAlias -> RoomAlias -> Bool)
-> (RoomAlias -> RoomAlias -> Bool) -> Eq RoomAlias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoomAlias -> RoomAlias -> Bool
$c/= :: RoomAlias -> RoomAlias -> Bool
== :: RoomAlias -> RoomAlias -> Bool
$c== :: RoomAlias -> RoomAlias -> Bool
Eq, Eq RoomAlias
Eq RoomAlias
-> (RoomAlias -> RoomAlias -> Ordering)
-> (RoomAlias -> RoomAlias -> Bool)
-> (RoomAlias -> RoomAlias -> Bool)
-> (RoomAlias -> RoomAlias -> Bool)
-> (RoomAlias -> RoomAlias -> Bool)
-> (RoomAlias -> RoomAlias -> RoomAlias)
-> (RoomAlias -> RoomAlias -> RoomAlias)
-> Ord RoomAlias
RoomAlias -> RoomAlias -> Bool
RoomAlias -> RoomAlias -> Ordering
RoomAlias -> RoomAlias -> RoomAlias
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RoomAlias -> RoomAlias -> RoomAlias
$cmin :: RoomAlias -> RoomAlias -> RoomAlias
max :: RoomAlias -> RoomAlias -> RoomAlias
$cmax :: RoomAlias -> RoomAlias -> RoomAlias
>= :: RoomAlias -> RoomAlias -> Bool
$c>= :: RoomAlias -> RoomAlias -> Bool
> :: RoomAlias -> RoomAlias -> Bool
$c> :: RoomAlias -> RoomAlias -> Bool
<= :: RoomAlias -> RoomAlias -> Bool
$c<= :: RoomAlias -> RoomAlias -> Bool
< :: RoomAlias -> RoomAlias -> Bool
$c< :: RoomAlias -> RoomAlias -> Bool
compare :: RoomAlias -> RoomAlias -> Ordering
$ccompare :: RoomAlias -> RoomAlias -> Ordering
$cp1Ord :: Eq RoomAlias
Ord, Eq RoomAlias
Eq RoomAlias
-> (Int -> RoomAlias -> Int)
-> (RoomAlias -> Int)
-> Hashable RoomAlias
Int -> RoomAlias -> Int
RoomAlias -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RoomAlias -> Int
$chash :: RoomAlias -> Int
hashWithSalt :: Int -> RoomAlias -> Int
$chashWithSalt :: Int -> RoomAlias -> Int
$cp1Hashable :: Eq RoomAlias
Hashable)

data ResolvedRoomAlias = ResolvedRoomAlias
  { ResolvedRoomAlias -> RoomAlias
roomAlias :: RoomAlias
  , ResolvedRoomAlias -> RoomID
roomID :: RoomID
  -- ^ The room ID for this room alias.
  , ResolvedRoomAlias -> [Text]
servers :: [T.Text]
  -- ^ A list of servers that are aware of this room alias.
  } deriving Int -> ResolvedRoomAlias -> ShowS
[ResolvedRoomAlias] -> ShowS
ResolvedRoomAlias -> String
(Int -> ResolvedRoomAlias -> ShowS)
-> (ResolvedRoomAlias -> String)
-> ([ResolvedRoomAlias] -> ShowS)
-> Show ResolvedRoomAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResolvedRoomAlias] -> ShowS
$cshowList :: [ResolvedRoomAlias] -> ShowS
show :: ResolvedRoomAlias -> String
$cshow :: ResolvedRoomAlias -> String
showsPrec :: Int -> ResolvedRoomAlias -> ShowS
$cshowsPrec :: Int -> ResolvedRoomAlias -> ShowS
Show

-- | Boilerplate data type for an aeson instance
data RoomAliasMetadata = RoomAliasMetadata
  { RoomAliasMetadata -> RoomID
ramRoomID :: RoomID
  , RoomAliasMetadata -> [Text]
ramServers :: [T.Text]
  }

instance FromJSON RoomAliasMetadata where
  parseJSON :: Value -> Parser RoomAliasMetadata
parseJSON = String
-> (Object -> Parser RoomAliasMetadata)
-> Value
-> Parser RoomAliasMetadata
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResolvedRoomAlias" ((Object -> Parser RoomAliasMetadata)
 -> Value -> Parser RoomAliasMetadata)
-> (Object -> Parser RoomAliasMetadata)
-> Value
-> Parser RoomAliasMetadata
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    RoomID
ramRoomID <- (Text -> RoomID) -> Parser Text -> Parser RoomID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> RoomID
RoomID (Parser Text -> Parser RoomID) -> Parser Text -> Parser RoomID
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"room_id"
    [Text]
ramServers <- Object
o Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"servers"
    RoomAliasMetadata -> Parser RoomAliasMetadata
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RoomAliasMetadata -> Parser RoomAliasMetadata)
-> RoomAliasMetadata -> Parser RoomAliasMetadata
forall a b. (a -> b) -> a -> b
$ RoomAliasMetadata :: RoomID -> [Text] -> RoomAliasMetadata
RoomAliasMetadata {[Text]
RoomID
ramServers :: [Text]
ramRoomID :: RoomID
ramServers :: [Text]
ramRoomID :: RoomID
..}

-- | Requests that the server resolve a room alias to a room ID.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3directoryroomroomalias
resolveRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ResolvedRoomAlias
resolveRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ResolvedRoomAlias
resolveRoomAlias ClientSession
session r :: RoomAlias
r@(RoomAlias Text
alias) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/directory/room/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeUriComponent Text
alias
  Either MatrixError RoomAliasMetadata
resp <- ClientSession -> Request -> MatrixIO RoomAliasMetadata
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO RoomAliasMetadata)
-> Request -> MatrixIO RoomAliasMetadata
forall a b. (a -> b) -> a -> b
$ Request
request { method :: ByteString
HTTP.method = ByteString
"GET" }
  case Either MatrixError RoomAliasMetadata
resp of
    Left MatrixError
err -> Either MatrixError ResolvedRoomAlias -> MatrixIO ResolvedRoomAlias
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either MatrixError ResolvedRoomAlias
 -> MatrixIO ResolvedRoomAlias)
-> Either MatrixError ResolvedRoomAlias
-> MatrixIO ResolvedRoomAlias
forall a b. (a -> b) -> a -> b
$ MatrixError -> Either MatrixError ResolvedRoomAlias
forall a b. a -> Either a b
Left MatrixError
err
    Right RoomAliasMetadata {[Text]
RoomID
ramServers :: [Text]
ramRoomID :: RoomID
ramServers :: RoomAliasMetadata -> [Text]
ramRoomID :: RoomAliasMetadata -> RoomID
..} -> Either MatrixError ResolvedRoomAlias -> MatrixIO ResolvedRoomAlias
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either MatrixError ResolvedRoomAlias
 -> MatrixIO ResolvedRoomAlias)
-> Either MatrixError ResolvedRoomAlias
-> MatrixIO ResolvedRoomAlias
forall a b. (a -> b) -> a -> b
$ ResolvedRoomAlias -> Either MatrixError ResolvedRoomAlias
forall a b. b -> Either a b
Right (ResolvedRoomAlias -> Either MatrixError ResolvedRoomAlias)
-> ResolvedRoomAlias -> Either MatrixError ResolvedRoomAlias
forall a b. (a -> b) -> a -> b
$ RoomAlias -> RoomID -> [Text] -> ResolvedRoomAlias
ResolvedRoomAlias RoomAlias
r RoomID
ramRoomID [Text]
ramServers

-- | Create a mapping of room alias to room ID.
-- https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3directoryroomroomalias
setRoomAlias :: ClientSession -> RoomAlias -> RoomID -> MatrixIO ()
setRoomAlias :: ClientSession -> RoomAlias -> RoomID -> MatrixIO ()
setRoomAlias ClientSession
session (RoomAlias Text
alias) (RoomID Text
roomId)= do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/directory/room/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeUriComponent Text
alias
  ClientSession -> Request -> MatrixIO ()
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest
    ClientSession
session (Request -> MatrixIO ()) -> Request -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"PUT"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode (Value -> ByteString) -> Value -> ByteString
forall a b. (a -> b) -> a -> b
$ [Pair] -> Value
object [(Key
"room_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
roomId)]
              }
-- | Delete a mapping of room alias to room ID.
-- https://spec.matrix.org/v1.1/client-server-api/#delete_matrixclientv3directoryroomroomalias
deleteRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ()
deleteRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ()
deleteRoomAlias ClientSession
session (RoomAlias Text
alias) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/directory/room/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
escapeUriComponent Text
alias
  ClientSession -> Request -> MatrixIO ()
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO ()) -> Request -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$ Request
request { method :: ByteString
HTTP.method = ByteString
"DELETE" }

data ResolvedAliases = ResolvedAliases [RoomAlias]

instance FromJSON ResolvedAliases where
  parseJSON :: Value -> Parser ResolvedAliases
parseJSON = String
-> (Object -> Parser ResolvedAliases)
-> Value
-> Parser ResolvedAliases
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResolvedAliases" ((Object -> Parser ResolvedAliases)
 -> Value -> Parser ResolvedAliases)
-> (Object -> Parser ResolvedAliases)
-> Value
-> Parser ResolvedAliases
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    [Text]
aliases <- Object
o Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"aliases"
    ResolvedAliases -> Parser ResolvedAliases
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ResolvedAliases -> Parser ResolvedAliases)
-> ResolvedAliases -> Parser ResolvedAliases
forall a b. (a -> b) -> a -> b
$ [RoomAlias] -> ResolvedAliases
ResolvedAliases (Text -> RoomAlias
RoomAlias (Text -> RoomAlias) -> [Text] -> [RoomAlias]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
aliases)
    
-- | Get a list of aliases maintained by the local server for the given room.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3roomsroomidaliases
getRoomAliases :: ClientSession -> RoomID -> MatrixIO [RoomAlias]
getRoomAliases :: ClientSession -> RoomID -> MatrixIO [RoomAlias]
getRoomAliases ClientSession
session (RoomID Text
rid) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/aliases"
  Either MatrixError ResolvedAliases
resp <- ClientSession -> Request -> MatrixIO ResolvedAliases
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest
    ClientSession
session (Request -> MatrixIO ResolvedAliases)
-> Request -> MatrixIO ResolvedAliases
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"GET" }
  case Either MatrixError ResolvedAliases
resp of
    Left MatrixError
err -> Either MatrixError [RoomAlias] -> MatrixIO [RoomAlias]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either MatrixError [RoomAlias] -> MatrixIO [RoomAlias])
-> Either MatrixError [RoomAlias] -> MatrixIO [RoomAlias]
forall a b. (a -> b) -> a -> b
$ MatrixError -> Either MatrixError [RoomAlias]
forall a b. a -> Either a b
Left MatrixError
err
    Right (ResolvedAliases [RoomAlias]
aliases) -> Either MatrixError [RoomAlias] -> MatrixIO [RoomAlias]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either MatrixError [RoomAlias] -> MatrixIO [RoomAlias])
-> Either MatrixError [RoomAlias] -> MatrixIO [RoomAlias]
forall a b. (a -> b) -> a -> b
$ [RoomAlias] -> Either MatrixError [RoomAlias]
forall a b. b -> Either a b
Right [RoomAlias]
aliases
-- | A newtype wrapper to decoded nested list
--
-- >>> decode "{\"joined_rooms\": [\"!foo:example.com\"]}" :: Maybe JoinedRooms
-- Just (JoinedRooms {unRooms = [RoomID "!foo:example.com"]})
newtype JoinedRooms = JoinedRooms {JoinedRooms -> [RoomID]
unRooms :: [RoomID]} deriving (Int -> JoinedRooms -> ShowS
[JoinedRooms] -> ShowS
JoinedRooms -> String
(Int -> JoinedRooms -> ShowS)
-> (JoinedRooms -> String)
-> ([JoinedRooms] -> ShowS)
-> Show JoinedRooms
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinedRooms] -> ShowS
$cshowList :: [JoinedRooms] -> ShowS
show :: JoinedRooms -> String
$cshow :: JoinedRooms -> String
showsPrec :: Int -> JoinedRooms -> ShowS
$cshowsPrec :: Int -> JoinedRooms -> ShowS
Show)

instance FromJSON JoinedRooms where
  parseJSON :: Value -> Parser JoinedRooms
parseJSON (Object Object
v) = do
    [Text]
rooms <- Object
v Object -> Key -> Parser [Text]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"joined_rooms"
    JoinedRooms -> Parser JoinedRooms
forall (f :: * -> *) a. Applicative f => a -> f a
pure (JoinedRooms -> Parser JoinedRooms)
-> ([RoomID] -> JoinedRooms) -> [RoomID] -> Parser JoinedRooms
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RoomID] -> JoinedRooms
JoinedRooms ([RoomID] -> Parser JoinedRooms) -> [RoomID] -> Parser JoinedRooms
forall a b. (a -> b) -> a -> b
$ Text -> RoomID
RoomID (Text -> RoomID) -> [Text] -> [RoomID]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text]
rooms
  parseJSON Value
_ = Parser JoinedRooms
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | Returns a list of the user’s current rooms.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3joined_rooms
getJoinedRooms :: ClientSession -> MatrixIO [RoomID]
getJoinedRooms :: ClientSession -> MatrixIO [RoomID]
getJoinedRooms ClientSession
session = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
"/_matrix/client/r0/joined_rooms"
  Either MatrixError JoinedRooms
response <- ClientSession -> Request -> MatrixIO JoinedRooms
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session Request
request
  Either MatrixError [RoomID] -> MatrixIO [RoomID]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either MatrixError [RoomID] -> MatrixIO [RoomID])
-> Either MatrixError [RoomID] -> MatrixIO [RoomID]
forall a b. (a -> b) -> a -> b
$ JoinedRooms -> [RoomID]
unRooms (JoinedRooms -> [RoomID])
-> Either MatrixError JoinedRooms -> Either MatrixError [RoomID]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either MatrixError JoinedRooms
response

newtype RoomID = RoomID T.Text deriving (Int -> RoomID -> ShowS
[RoomID] -> ShowS
RoomID -> String
(Int -> RoomID -> ShowS)
-> (RoomID -> String) -> ([RoomID] -> ShowS) -> Show RoomID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoomID] -> ShowS
$cshowList :: [RoomID] -> ShowS
show :: RoomID -> String
$cshow :: RoomID -> String
showsPrec :: Int -> RoomID -> ShowS
$cshowsPrec :: Int -> RoomID -> ShowS
Show, RoomID -> RoomID -> Bool
(RoomID -> RoomID -> Bool)
-> (RoomID -> RoomID -> Bool) -> Eq RoomID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoomID -> RoomID -> Bool
$c/= :: RoomID -> RoomID -> Bool
== :: RoomID -> RoomID -> Bool
$c== :: RoomID -> RoomID -> Bool
Eq, Eq RoomID
Eq RoomID
-> (RoomID -> RoomID -> Ordering)
-> (RoomID -> RoomID -> Bool)
-> (RoomID -> RoomID -> Bool)
-> (RoomID -> RoomID -> Bool)
-> (RoomID -> RoomID -> Bool)
-> (RoomID -> RoomID -> RoomID)
-> (RoomID -> RoomID -> RoomID)
-> Ord RoomID
RoomID -> RoomID -> Bool
RoomID -> RoomID -> Ordering
RoomID -> RoomID -> RoomID
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RoomID -> RoomID -> RoomID
$cmin :: RoomID -> RoomID -> RoomID
max :: RoomID -> RoomID -> RoomID
$cmax :: RoomID -> RoomID -> RoomID
>= :: RoomID -> RoomID -> Bool
$c>= :: RoomID -> RoomID -> Bool
> :: RoomID -> RoomID -> Bool
$c> :: RoomID -> RoomID -> Bool
<= :: RoomID -> RoomID -> Bool
$c<= :: RoomID -> RoomID -> Bool
< :: RoomID -> RoomID -> Bool
$c< :: RoomID -> RoomID -> Bool
compare :: RoomID -> RoomID -> Ordering
$ccompare :: RoomID -> RoomID -> Ordering
$cp1Ord :: Eq RoomID
Ord, Eq RoomID
Eq RoomID
-> (Int -> RoomID -> Int) -> (RoomID -> Int) -> Hashable RoomID
Int -> RoomID -> Int
RoomID -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RoomID -> Int
$chash :: RoomID -> Int
hashWithSalt :: Int -> RoomID -> Int
$chashWithSalt :: Int -> RoomID -> Int
$cp1Hashable :: Eq RoomID
Hashable)

instance FromJSON RoomID where
  parseJSON :: Value -> Parser RoomID
parseJSON (Object Object
v) = Text -> RoomID
RoomID (Text -> RoomID) -> Parser Text -> Parser RoomID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"room_id"
  parseJSON Value
_ = Parser RoomID
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | Invites a user to participate in a particular room. They do not
-- start participating in the room until they actually join the room.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidinvite
inviteToRoom :: ClientSession -> RoomID -> UserID -> Maybe T.Text -> MatrixIO ()
inviteToRoom :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
inviteToRoom ClientSession
session (RoomID Text
rid) (UserID Text
uid) Maybe Text
reason = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/invite"
  let body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [(Key
"user_id", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
uid)] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [(Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"reason",) (Value -> Pair) -> (Text -> Value) -> Text -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Text
reason]
  ClientSession -> Request -> MatrixIO ()
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO ()) -> Request -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"POST"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
              }

-- | Note that this API takes either a room ID or alias, unlike 'joinRoomById'
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3joinroomidoralias
joinRoom :: ClientSession -> T.Text -> MatrixIO RoomID
joinRoom :: ClientSession -> Text -> MatrixIO RoomID
joinRoom ClientSession
session Text
roomName = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/r0/join/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomNameUrl
  ClientSession -> Request -> MatrixIO RoomID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request
request {method :: ByteString
HTTP.method = ByteString
"POST"})
  where
    roomNameUrl :: Text
roomNameUrl = ByteString -> Text
decodeUtf8 (ByteString -> Text) -> (Text -> ByteString) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> ByteString -> ByteString
urlEncode Bool
True (ByteString -> ByteString)
-> (Text -> ByteString) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
roomName

-- | Starts a user participating in a particular room, if that user is
-- allowed to participate in that room.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidjoin
joinRoomById :: ClientSession -> RoomID -> MatrixIO RoomID
joinRoomById :: ClientSession -> RoomID -> MatrixIO RoomID
joinRoomById ClientSession
session (RoomID Text
roomId) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/r0/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/join"
  ClientSession -> Request -> MatrixIO RoomID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request
request {method :: ByteString
HTTP.method = ByteString
"POST"})

-- | This API “knocks” on the room to ask for permission to join, if
-- the user is allowed to knock on the room.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3knockroomidoralias
knockOnRoom :: ClientSession -> Either RoomID RoomAlias -> [T.Text] -> Maybe T.Text -> MatrixIO RoomID
knockOnRoom :: ClientSession
-> Either RoomID RoomAlias
-> [Text]
-> Maybe Text
-> MatrixIO RoomID
knockOnRoom ClientSession
session Either RoomID RoomAlias
room [Text]
servers Maybe Text
reason = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
" /_matrix/client/v3/knock/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Either Text Text -> Text
forall x. Either x x -> x
indistinct ((RoomID -> Text)
-> (RoomAlias -> Text)
-> Either RoomID RoomAlias
-> Either Text Text
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap RoomID -> Text
coerce RoomAlias -> Text
coerce Either RoomID RoomAlias
room)
  let body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [(Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"reason",) (Value -> Pair) -> (Text -> Value) -> Text -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Text
reason]
  ClientSession -> Request -> MatrixIO RoomID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO RoomID) -> Request -> MatrixIO RoomID
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"POST"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
              , queryString :: ByteString
HTTP.queryString = Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Text
"?server_name=" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat (Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"," [Text]
servers)
              }

-- | Stops remembering a particular room.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidforget
forgetRoom :: ClientSession -> RoomID -> MatrixIO ()
forgetRoom :: ClientSession -> RoomID -> MatrixIO ()
forgetRoom ClientSession
session (RoomID Text
roomId) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/forget"
  (Value -> ()) -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ()
ensureEmptyObject (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ClientSession -> Request -> IO (Either MatrixError Value)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request
request {method :: ByteString
HTTP.method = ByteString
"POST"})
  where
    ensureEmptyObject :: Value -> ()
    ensureEmptyObject :: Value -> ()
ensureEmptyObject Value
value = case Value
value of
      Object Object
xs | Object
xs Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty -> ()
      Value
_anyOther -> String -> ()
forall a. HasCallStack => String -> a
error (String -> ()) -> String -> ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown forget response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
value
     

-- | Stop participating in a particular room.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidleave
leaveRoomById :: ClientSession -> RoomID -> MatrixIO ()
leaveRoomById :: ClientSession -> RoomID -> MatrixIO ()
leaveRoomById ClientSession
session (RoomID Text
roomId) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/r0/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/leave"
  (Value -> ()) -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ()
ensureEmptyObject (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ClientSession -> Request -> IO (Either MatrixError Value)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request
request {method :: ByteString
HTTP.method = ByteString
"POST"})
  where
    ensureEmptyObject :: Value -> ()
    ensureEmptyObject :: Value -> ()
ensureEmptyObject Value
value = case Value
value of
      Object Object
xs | Object
xs Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty -> ()
      Value
_anyOther -> String -> ()
forall a. HasCallStack => String -> a
error (String -> ()) -> String -> ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown leave response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
value

-- | Kick a user from the room.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidkick
kickUser :: ClientSession -> RoomID -> UserID -> Maybe T.Text -> MatrixIO ()
kickUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
kickUser ClientSession
session (RoomID Text
roomId) (UserID Text
uid) Maybe Text
reason = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/kick"
  let body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [(Key
"user_id", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
uid)] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [(Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"reason",) (Value -> Pair) -> (Text -> Value) -> Text -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Text
reason]
  (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Value -> ()) -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ()
ensureEmptyObject) (IO (Either MatrixError Value) -> MatrixIO ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$ ClientSession -> Request -> IO (Either MatrixError Value)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> IO (Either MatrixError Value))
-> Request -> IO (Either MatrixError Value)
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"POST"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
              }
  where
    ensureEmptyObject :: Value -> ()
    ensureEmptyObject :: Value -> ()
ensureEmptyObject Value
value = case Value
value of
      Object Object
xs | Object
xs Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty -> ()
      Value
_anyOther -> String -> ()
forall a. HasCallStack => String -> a
error (String -> ()) -> String -> ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown leave response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
value

-- | Ban a user in the room. If the user is currently in the room, also kick them.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidban
banUser :: ClientSession -> RoomID -> UserID -> Maybe T.Text -> MatrixIO ()
banUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
banUser ClientSession
session (RoomID Text
roomId) (UserID Text
uid) Maybe Text
reason = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/ban"
  let body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [(Key
"user_id", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
uid)] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [(Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"reason",) (Value -> Pair) -> (Text -> Value) -> Text -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Text
reason]
  (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Value -> ()) -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ()
ensureEmptyObject) (IO (Either MatrixError Value) -> MatrixIO ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$ ClientSession -> Request -> IO (Either MatrixError Value)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> IO (Either MatrixError Value))
-> Request -> IO (Either MatrixError Value)
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"POST"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
              }
  where
    ensureEmptyObject :: Value -> ()
    ensureEmptyObject :: Value -> ()
ensureEmptyObject Value
value = case Value
value of
      Object Object
xs | Object
xs Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty -> ()
      Value
_anyOther -> String -> ()
forall a. HasCallStack => String -> a
error (String -> ()) -> String -> ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown leave response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
value

-- | Unban a user from the room. This allows them to be invited to the
-- room, and join if they would otherwise be allowed to join according
-- to its join rules.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidunban
unbanUser :: ClientSession -> RoomID -> UserID -> Maybe T.Text -> MatrixIO ()
unbanUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
unbanUser ClientSession
session (RoomID Text
roomId) (UserID Text
uid) Maybe Text
reason = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/rooms/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomId Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/unban"
  let body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [(Key
"user_id", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
uid)] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [(Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"reason",) (Value -> Pair) -> (Text -> Value) -> Text -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Text
reason]
  (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Value -> ()) -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ()
ensureEmptyObject) (IO (Either MatrixError Value) -> MatrixIO ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$ ClientSession -> Request -> IO (Either MatrixError Value)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> IO (Either MatrixError Value))
-> Request -> IO (Either MatrixError Value)
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"POST"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
              }
  where
    ensureEmptyObject :: Value -> ()
    ensureEmptyObject :: Value -> ()
ensureEmptyObject Value
value = case Value
value of
      Object Object
xs | Object
xs Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty -> ()
      Value
_anyOther -> String -> ()
forall a. HasCallStack => String -> a
error (String -> ()) -> String -> ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown leave response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
value

data Visibility = Public | Private
  deriving (Int -> Visibility -> ShowS
[Visibility] -> ShowS
Visibility -> String
(Int -> Visibility -> ShowS)
-> (Visibility -> String)
-> ([Visibility] -> ShowS)
-> Show Visibility
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Visibility] -> ShowS
$cshowList :: [Visibility] -> ShowS
show :: Visibility -> String
$cshow :: Visibility -> String
showsPrec :: Int -> Visibility -> ShowS
$cshowsPrec :: Int -> Visibility -> ShowS
Show)

instance ToJSON Visibility where
  toJSON :: Visibility -> Value
toJSON = \case
    Visibility
Public -> Text -> Value
String Text
"public"
    Visibility
Private -> Text -> Value
String Text
"private"

instance FromJSON Visibility where
  parseJSON :: Value -> Parser Visibility
parseJSON = String -> (Text -> Parser Visibility) -> Value -> Parser Visibility
forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"Visibility" ((Text -> Parser Visibility) -> Value -> Parser Visibility)
-> (Text -> Parser Visibility) -> Value -> Parser Visibility
forall a b. (a -> b) -> a -> b
$ \case
    Text
"public" -> Visibility -> Parser Visibility
forall (f :: * -> *) a. Applicative f => a -> f a
pure Visibility
Public
    Text
"private" -> Visibility -> Parser Visibility
forall (f :: * -> *) a. Applicative f => a -> f a
pure Visibility
Private
    Text
_ -> Parser Visibility
forall (m :: * -> *) a. MonadPlus m => m a
mzero

newtype GetVisibility = GetVisibility { GetVisibility -> Visibility
getVisibility :: Visibility }

instance FromJSON GetVisibility where
  parseJSON :: Value -> Parser GetVisibility
parseJSON = String
-> (Object -> Parser GetVisibility)
-> Value
-> Parser GetVisibility
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetVisibility" ((Object -> Parser GetVisibility) -> Value -> Parser GetVisibility)
-> (Object -> Parser GetVisibility)
-> Value
-> Parser GetVisibility
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Visibility
getVisibility <- Object
o Object -> Key -> Parser Visibility
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"visibility"
    GetVisibility -> Parser GetVisibility
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GetVisibility -> Parser GetVisibility)
-> GetVisibility -> Parser GetVisibility
forall a b. (a -> b) -> a -> b
$ GetVisibility :: Visibility -> GetVisibility
GetVisibility {Visibility
getVisibility :: Visibility
getVisibility :: Visibility
..}
    
-- | Gets the visibility of a given room on the server’s public room directory.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3directorylistroomroomid
checkRoomVisibility :: ClientSession -> RoomID -> MatrixIO Visibility
checkRoomVisibility :: ClientSession -> RoomID -> MatrixIO Visibility
checkRoomVisibility ClientSession
session (RoomID Text
rid) = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/directory/list/room/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid
  (Either MatrixError GetVisibility -> Either MatrixError Visibility)
-> IO (Either MatrixError GetVisibility) -> MatrixIO Visibility
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((GetVisibility -> Visibility)
-> Either MatrixError GetVisibility
-> Either MatrixError Visibility
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap GetVisibility -> Visibility
getVisibility) (IO (Either MatrixError GetVisibility) -> MatrixIO Visibility)
-> IO (Either MatrixError GetVisibility) -> MatrixIO Visibility
forall a b. (a -> b) -> a -> b
$ ClientSession -> Request -> IO (Either MatrixError GetVisibility)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session Request
request
    
-- | Sets the visibility of a given room in the server’s public room directory.
-- https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3directorylistroomroomid
setRoomVisibility :: ClientSession -> RoomID -> Visibility -> MatrixIO ()
setRoomVisibility :: ClientSession -> RoomID -> Visibility -> MatrixIO ()
setRoomVisibility ClientSession
session (RoomID Text
rid) Visibility
visibility = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ Text
"/_matrix/client/v3/directory/list/room/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
rid
  let body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [(Key
"visibility", Visibility -> Value
forall a. ToJSON a => a -> Value
toJSON Visibility
visibility)]
  (Either MatrixError Value -> Either MatrixError ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Value -> ()) -> Either MatrixError Value -> Either MatrixError ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> ()
ensureEmptyObject) (IO (Either MatrixError Value) -> MatrixIO ())
-> IO (Either MatrixError Value) -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$ ClientSession -> Request -> IO (Either MatrixError Value)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> IO (Either MatrixError Value))
-> Request -> IO (Either MatrixError Value)
forall a b. (a -> b) -> a -> b
$
      Request
request { method :: ByteString
HTTP.method = ByteString
"PUT"
              , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
              }
  where
    ensureEmptyObject :: Value -> ()
    ensureEmptyObject :: Value -> ()
ensureEmptyObject Value
value = case Value
value of
      Object Object
xs | Object
xs Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty -> ()
      Value
_anyOther -> String -> ()
forall a. HasCallStack => String -> a
error (String -> ()) -> String -> ()
forall a b. (a -> b) -> a -> b
$ String
"Unknown setRoomVisibility response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Value -> String
forall a. Show a => a -> String
show Value
value

-- | A pagination token from a previous request, allowing clients to
-- get the next (or previous) batch of rooms. The direction of
-- pagination is specified solely by which token is supplied, rather
-- than via an explicit flag.
newtype PaginationChunk = PaginationChunk { PaginationChunk -> Text
getChunk :: T.Text }
  deriving stock (Int -> PaginationChunk -> ShowS
[PaginationChunk] -> ShowS
PaginationChunk -> String
(Int -> PaginationChunk -> ShowS)
-> (PaginationChunk -> String)
-> ([PaginationChunk] -> ShowS)
-> Show PaginationChunk
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaginationChunk] -> ShowS
$cshowList :: [PaginationChunk] -> ShowS
show :: PaginationChunk -> String
$cshow :: PaginationChunk -> String
showsPrec :: Int -> PaginationChunk -> ShowS
$cshowsPrec :: Int -> PaginationChunk -> ShowS
Show)
  deriving newtype ([PaginationChunk] -> Encoding
[PaginationChunk] -> Value
PaginationChunk -> Encoding
PaginationChunk -> Value
(PaginationChunk -> Value)
-> (PaginationChunk -> Encoding)
-> ([PaginationChunk] -> Value)
-> ([PaginationChunk] -> Encoding)
-> ToJSON PaginationChunk
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PaginationChunk] -> Encoding
$ctoEncodingList :: [PaginationChunk] -> Encoding
toJSONList :: [PaginationChunk] -> Value
$ctoJSONList :: [PaginationChunk] -> Value
toEncoding :: PaginationChunk -> Encoding
$ctoEncoding :: PaginationChunk -> Encoding
toJSON :: PaginationChunk -> Value
$ctoJSON :: PaginationChunk -> Value
ToJSON, Value -> Parser [PaginationChunk]
Value -> Parser PaginationChunk
(Value -> Parser PaginationChunk)
-> (Value -> Parser [PaginationChunk]) -> FromJSON PaginationChunk
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PaginationChunk]
$cparseJSONList :: Value -> Parser [PaginationChunk]
parseJSON :: Value -> Parser PaginationChunk
$cparseJSON :: Value -> Parser PaginationChunk
FromJSON)

data Room = Room
  { Room -> Maybe [Text]
aliases :: Maybe [T.Text]
  , Room -> Maybe Text
avatarUrl :: Maybe T.Text
  , Room -> Maybe Text
canonicalAlias :: Maybe T.Text
  , Room -> Bool
guestCanJoin :: Bool
  , Room -> Maybe Text
joinRule :: Maybe T.Text
  , Room -> Maybe Text
name :: Maybe T.Text
  , Room -> Int
numJoinedMembers :: Int
  , Room -> RoomID
roomId :: RoomID
  , Room -> Maybe Text
topic :: Maybe T.Text
  , Room -> Bool
worldReadable :: Bool
  } deriving Int -> Room -> ShowS
[Room] -> ShowS
Room -> String
(Int -> Room -> ShowS)
-> (Room -> String) -> ([Room] -> ShowS) -> Show Room
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Room] -> ShowS
$cshowList :: [Room] -> ShowS
show :: Room -> String
$cshow :: Room -> String
showsPrec :: Int -> Room -> ShowS
$cshowsPrec :: Int -> Room -> ShowS
Show

instance FromJSON Room where
  parseJSON :: Value -> Parser Room
parseJSON = String -> (Object -> Parser Room) -> Value -> Parser Room
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Room" ((Object -> Parser Room) -> Value -> Parser Room)
-> (Object -> Parser Room) -> Value -> Parser Room
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    Maybe [Text]
aliases <- Object
o Object -> Key -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"aliases" 
    Maybe Text
avatarUrl <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"avatar_url"
    Maybe Text
canonicalAlias <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"canonical_alias"
    Bool
guestCanJoin <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"guest_can_join"
    Maybe Text
joinRule <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"join_rule"
    Maybe Text
name <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"name"
    Int
numJoinedMembers <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"num_joined_members"
    RoomID
roomId <- (Text -> RoomID) -> Parser Text -> Parser RoomID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> RoomID
RoomID (Parser Text -> Parser RoomID) -> Parser Text -> Parser RoomID
forall a b. (a -> b) -> a -> b
$ Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"room_id"
    Maybe Text
topic <- Object
o Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"topic"
    Bool
worldReadable <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"world_readable"
    Room -> Parser Room
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Room -> Parser Room) -> Room -> Parser Room
forall a b. (a -> b) -> a -> b
$ Room :: Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Bool
-> Maybe Text
-> Maybe Text
-> Int
-> RoomID
-> Maybe Text
-> Bool
-> Room
Room {Bool
Int
Maybe [Text]
Maybe Text
RoomID
worldReadable :: Bool
topic :: Maybe Text
roomId :: RoomID
numJoinedMembers :: Int
name :: Maybe Text
joinRule :: Maybe Text
guestCanJoin :: Bool
canonicalAlias :: Maybe Text
avatarUrl :: Maybe Text
aliases :: Maybe [Text]
worldReadable :: Bool
topic :: Maybe Text
roomId :: RoomID
numJoinedMembers :: Int
name :: Maybe Text
joinRule :: Maybe Text
guestCanJoin :: Bool
canonicalAlias :: Maybe Text
avatarUrl :: Maybe Text
aliases :: Maybe [Text]
..}

data PublicRooms = PublicRooms
  { PublicRooms -> [Room]
prChunk :: [Room]
  , PublicRooms -> Maybe PaginationChunk
prNextBatch :: Maybe PaginationChunk
  , PublicRooms -> Maybe PaginationChunk
prPrevBatch :: Maybe PaginationChunk
  , PublicRooms -> Maybe Int
prTotalRoomCountEstimate :: Maybe Int
  } deriving Int -> PublicRooms -> ShowS
[PublicRooms] -> ShowS
PublicRooms -> String
(Int -> PublicRooms -> ShowS)
-> (PublicRooms -> String)
-> ([PublicRooms] -> ShowS)
-> Show PublicRooms
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicRooms] -> ShowS
$cshowList :: [PublicRooms] -> ShowS
show :: PublicRooms -> String
$cshow :: PublicRooms -> String
showsPrec :: Int -> PublicRooms -> ShowS
$cshowsPrec :: Int -> PublicRooms -> ShowS
Show

instance FromJSON PublicRooms where
  parseJSON :: Value -> Parser PublicRooms
parseJSON = String
-> (Object -> Parser PublicRooms) -> Value -> Parser PublicRooms
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PublicRooms" ((Object -> Parser PublicRooms) -> Value -> Parser PublicRooms)
-> (Object -> Parser PublicRooms) -> Value -> Parser PublicRooms
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
    [Room]
prChunk <- Object
o Object -> Key -> Parser [Room]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"chunk"
    Maybe PaginationChunk
prNextBatch <- Object
o Object -> Key -> Parser (Maybe PaginationChunk)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"next_batch"
    Maybe PaginationChunk
prPrevBatch <- Object
o Object -> Key -> Parser (Maybe PaginationChunk)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"prev_batch"
    Maybe Int
prTotalRoomCountEstimate <- Object
o Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"total_room_count_estimate"
    PublicRooms -> Parser PublicRooms
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PublicRooms -> Parser PublicRooms)
-> PublicRooms -> Parser PublicRooms
forall a b. (a -> b) -> a -> b
$ PublicRooms :: [Room]
-> Maybe PaginationChunk
-> Maybe PaginationChunk
-> Maybe Int
-> PublicRooms
PublicRooms {[Room]
Maybe Int
Maybe PaginationChunk
prTotalRoomCountEstimate :: Maybe Int
prPrevBatch :: Maybe PaginationChunk
prNextBatch :: Maybe PaginationChunk
prChunk :: [Room]
prTotalRoomCountEstimate :: Maybe Int
prPrevBatch :: Maybe PaginationChunk
prNextBatch :: Maybe PaginationChunk
prChunk :: [Room]
..}

-- | Lists the public rooms on the server.
-- https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3publicrooms
getPublicRooms :: ClientSession -> Maybe Int -> Maybe PaginationChunk -> MatrixIO PublicRooms
getPublicRooms :: ClientSession
-> Maybe Int -> Maybe PaginationChunk -> MatrixIO PublicRooms
getPublicRooms ClientSession
session Maybe Int
limit Maybe PaginationChunk
chunk = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
"/_matrix/client/v3/publicRooms"
  let since :: Maybe Text
since = (PaginationChunk -> Text) -> Maybe PaginationChunk -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend Text
"since=" (Text -> Text)
-> (PaginationChunk -> Text) -> PaginationChunk -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PaginationChunk -> Text
getChunk) Maybe PaginationChunk
chunk
      limit' :: Maybe Text
limit' = (Int -> Text) -> Maybe Int -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend Text
"limit=" (Text -> Text) -> (Int -> Text) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text
forall a. Show a => a -> Text
tshow) Maybe Int
limit
      queryString :: ByteString
queryString = Text -> ByteString
encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"&" ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Maybe Text] -> [Text]
forall a. [Maybe a] -> [a]
catMaybes [Maybe Text
since, Maybe Text
limit']
  ClientSession -> Request -> MatrixIO PublicRooms
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO PublicRooms)
-> Request -> MatrixIO PublicRooms
forall a b. (a -> b) -> a -> b
$
    Request
request { queryString :: ByteString
HTTP.queryString = ByteString
queryString }

newtype ThirdPartyInstanceId = ThirdPartyInstanceId T.Text
  deriving (Value -> Parser [ThirdPartyInstanceId]
Value -> Parser ThirdPartyInstanceId
(Value -> Parser ThirdPartyInstanceId)
-> (Value -> Parser [ThirdPartyInstanceId])
-> FromJSON ThirdPartyInstanceId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ThirdPartyInstanceId]
$cparseJSONList :: Value -> Parser [ThirdPartyInstanceId]
parseJSON :: Value -> Parser ThirdPartyInstanceId
$cparseJSON :: Value -> Parser ThirdPartyInstanceId
FromJSON, [ThirdPartyInstanceId] -> Encoding
[ThirdPartyInstanceId] -> Value
ThirdPartyInstanceId -> Encoding
ThirdPartyInstanceId -> Value
(ThirdPartyInstanceId -> Value)
-> (ThirdPartyInstanceId -> Encoding)
-> ([ThirdPartyInstanceId] -> Value)
-> ([ThirdPartyInstanceId] -> Encoding)
-> ToJSON ThirdPartyInstanceId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ThirdPartyInstanceId] -> Encoding
$ctoEncodingList :: [ThirdPartyInstanceId] -> Encoding
toJSONList :: [ThirdPartyInstanceId] -> Value
$ctoJSONList :: [ThirdPartyInstanceId] -> Value
toEncoding :: ThirdPartyInstanceId -> Encoding
$ctoEncoding :: ThirdPartyInstanceId -> Encoding
toJSON :: ThirdPartyInstanceId -> Value
$ctoJSON :: ThirdPartyInstanceId -> Value
ToJSON)

-- | Lists the public rooms on the server, with optional filter.
-- https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3publicrooms
getPublicRooms' :: ClientSession -> Maybe Int -> Maybe PaginationChunk -> Maybe T.Text -> Maybe Bool -> Maybe ThirdPartyInstanceId-> MatrixIO PublicRooms
getPublicRooms' :: ClientSession
-> Maybe Int
-> Maybe PaginationChunk
-> Maybe Text
-> Maybe Bool
-> Maybe ThirdPartyInstanceId
-> MatrixIO PublicRooms
getPublicRooms' ClientSession
session Maybe Int
limit Maybe PaginationChunk
chunk Maybe Text
searchTerm Maybe Bool
includeAllNetworks Maybe ThirdPartyInstanceId
thirdPartyId = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
"/_matrix/client/v3/publicRooms"
  let filter' :: Value
filter' = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [ (Text -> Pair) -> Maybe Text -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"generic_search_term",) (Value -> Pair) -> (Text -> Value) -> Text -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Text
searchTerm]
      since :: Maybe Pair
since = (PaginationChunk -> Pair) -> Maybe PaginationChunk -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"since",) (Value -> Pair)
-> (PaginationChunk -> Value) -> PaginationChunk -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PaginationChunk -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe PaginationChunk
chunk
      limit' :: Maybe Pair
limit' = (Int -> Pair) -> Maybe Int -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"limit",) (Value -> Pair) -> (Int -> Value) -> Int -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Int
limit
      includeAllNetworks' :: Maybe Pair
includeAllNetworks' = (Bool -> Pair) -> Maybe Bool -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"include_all_networks",) (Value -> Pair) -> (Bool -> Value) -> Bool -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe Bool
includeAllNetworks
      thirdPartyId' :: Maybe Pair
thirdPartyId' = (ThirdPartyInstanceId -> Pair)
-> Maybe ThirdPartyInstanceId -> Maybe Pair
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Key
"third_party_instance_id",) (Value -> Pair)
-> (ThirdPartyInstanceId -> Value) -> ThirdPartyInstanceId -> Pair
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ThirdPartyInstanceId -> Value
forall a. ToJSON a => a -> Value
toJSON) Maybe ThirdPartyInstanceId
thirdPartyId
      body :: Value
body = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ [(Key
"filter", Value
filter')] [Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Maybe Pair] -> [Pair]
forall a. [Maybe a] -> [a]
catMaybes [ Maybe Pair
since, Maybe Pair
limit', Maybe Pair
includeAllNetworks', Maybe Pair
thirdPartyId' ]
  ClientSession -> Request -> MatrixIO PublicRooms
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO PublicRooms)
-> Request -> MatrixIO PublicRooms
forall a b. (a -> b) -> a -> b
$
    Request
request { method :: ByteString
HTTP.method = ByteString
"POST"
            , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode Value
body
            }
  
-------------------------------------------------------------------------------
-- https://matrix.org/docs/spec/client_server/latest#post-matrix-client-r0-user-userid-filter
newtype FilterID = FilterID T.Text deriving (Int -> FilterID -> ShowS
[FilterID] -> ShowS
FilterID -> String
(Int -> FilterID -> ShowS)
-> (FilterID -> String) -> ([FilterID] -> ShowS) -> Show FilterID
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilterID] -> ShowS
$cshowList :: [FilterID] -> ShowS
show :: FilterID -> String
$cshow :: FilterID -> String
showsPrec :: Int -> FilterID -> ShowS
$cshowsPrec :: Int -> FilterID -> ShowS
Show, FilterID -> FilterID -> Bool
(FilterID -> FilterID -> Bool)
-> (FilterID -> FilterID -> Bool) -> Eq FilterID
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterID -> FilterID -> Bool
$c/= :: FilterID -> FilterID -> Bool
== :: FilterID -> FilterID -> Bool
$c== :: FilterID -> FilterID -> Bool
Eq, Eq FilterID
Eq FilterID
-> (Int -> FilterID -> Int)
-> (FilterID -> Int)
-> Hashable FilterID
Int -> FilterID -> Int
FilterID -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: FilterID -> Int
$chash :: FilterID -> Int
hashWithSalt :: Int -> FilterID -> Int
$chashWithSalt :: Int -> FilterID -> Int
$cp1Hashable :: Eq FilterID
Hashable)

instance FromJSON FilterID where
  parseJSON :: Value -> Parser FilterID
parseJSON (Object Object
v) = Text -> FilterID
FilterID (Text -> FilterID) -> Parser Text -> Parser FilterID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"filter_id"
  parseJSON Value
_ = Parser FilterID
forall (m :: * -> *) a. MonadPlus m => m a
mzero

data EventFormat = Client | Federation deriving (Int -> EventFormat -> ShowS
[EventFormat] -> ShowS
EventFormat -> String
(Int -> EventFormat -> ShowS)
-> (EventFormat -> String)
-> ([EventFormat] -> ShowS)
-> Show EventFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventFormat] -> ShowS
$cshowList :: [EventFormat] -> ShowS
show :: EventFormat -> String
$cshow :: EventFormat -> String
showsPrec :: Int -> EventFormat -> ShowS
$cshowsPrec :: Int -> EventFormat -> ShowS
Show, EventFormat -> EventFormat -> Bool
(EventFormat -> EventFormat -> Bool)
-> (EventFormat -> EventFormat -> Bool) -> Eq EventFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventFormat -> EventFormat -> Bool
$c/= :: EventFormat -> EventFormat -> Bool
== :: EventFormat -> EventFormat -> Bool
$c== :: EventFormat -> EventFormat -> Bool
Eq)

instance ToJSON EventFormat where
  toJSON :: EventFormat -> Value
toJSON EventFormat
ef = case EventFormat
ef of
    EventFormat
Client -> Value
"client"
    EventFormat
Federation -> Value
"federation"

instance FromJSON EventFormat where
  parseJSON :: Value -> Parser EventFormat
parseJSON Value
v = case Value
v of
    (String Text
"client") -> EventFormat -> Parser EventFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure EventFormat
Client
    (String Text
"federation") -> EventFormat -> Parser EventFormat
forall (f :: * -> *) a. Applicative f => a -> f a
pure EventFormat
Federation
    Value
_ -> Parser EventFormat
forall (m :: * -> *) a. MonadPlus m => m a
mzero

data EventFilter = EventFilter
  { EventFilter -> Maybe Int
efLimit :: Maybe Int,
    EventFilter -> Maybe [Text]
efNotSenders :: Maybe [T.Text],
    EventFilter -> Maybe [Text]
efNotTypes :: Maybe [T.Text],
    EventFilter -> Maybe [Text]
efSenders :: Maybe [T.Text],
    EventFilter -> Maybe [Text]
efTypes :: Maybe [T.Text]
  }
  deriving (Int -> EventFilter -> ShowS
[EventFilter] -> ShowS
EventFilter -> String
(Int -> EventFilter -> ShowS)
-> (EventFilter -> String)
-> ([EventFilter] -> ShowS)
-> Show EventFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EventFilter] -> ShowS
$cshowList :: [EventFilter] -> ShowS
show :: EventFilter -> String
$cshow :: EventFilter -> String
showsPrec :: Int -> EventFilter -> ShowS
$cshowsPrec :: Int -> EventFilter -> ShowS
Show, EventFilter -> EventFilter -> Bool
(EventFilter -> EventFilter -> Bool)
-> (EventFilter -> EventFilter -> Bool) -> Eq EventFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventFilter -> EventFilter -> Bool
$c/= :: EventFilter -> EventFilter -> Bool
== :: EventFilter -> EventFilter -> Bool
$c== :: EventFilter -> EventFilter -> Bool
Eq, (forall x. EventFilter -> Rep EventFilter x)
-> (forall x. Rep EventFilter x -> EventFilter)
-> Generic EventFilter
forall x. Rep EventFilter x -> EventFilter
forall x. EventFilter -> Rep EventFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EventFilter x -> EventFilter
$cfrom :: forall x. EventFilter -> Rep EventFilter x
Generic)

defaultEventFilter :: EventFilter
defaultEventFilter :: EventFilter
defaultEventFilter = Maybe Int
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> EventFilter
EventFilter Maybe Int
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing

-- | A filter that should match nothing
eventFilterAll :: EventFilter
eventFilterAll :: EventFilter
eventFilterAll = EventFilter
defaultEventFilter {efLimit :: Maybe Int
efLimit = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0, efNotTypes :: Maybe [Text]
efNotTypes = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
"*"]}

aesonOptions :: Aeson.Options
aesonOptions :: Options
aesonOptions = (ShowS -> Options
aesonPrefix ShowS
snakeCase) {omitNothingFields :: Bool
Aeson.omitNothingFields = Bool
True}

instance ToJSON EventFilter where
  toJSON :: EventFilter -> Value
toJSON = Options -> EventFilter -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON EventFilter where
  parseJSON :: Value -> Parser EventFilter
parseJSON = Options -> Value -> Parser EventFilter
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

data RoomEventFilter = RoomEventFilter
  { RoomEventFilter -> Maybe Int
refLimit :: Maybe Int,
    RoomEventFilter -> Maybe [Text]
refNotSenders :: Maybe [T.Text],
    RoomEventFilter -> Maybe [Text]
refNotTypes :: Maybe [T.Text],
    RoomEventFilter -> Maybe [Text]
refSenders :: Maybe [T.Text],
    RoomEventFilter -> Maybe [Text]
refTypes :: Maybe [T.Text],
    RoomEventFilter -> Maybe Bool
refLazyLoadMembers :: Maybe Bool,
    RoomEventFilter -> Maybe Bool
refIncludeRedundantMembers :: Maybe Bool,
    RoomEventFilter -> Maybe [Text]
refNotRooms :: Maybe [T.Text],
    RoomEventFilter -> Maybe [Text]
refRooms :: Maybe [T.Text],
    RoomEventFilter -> Maybe Bool
refContainsUrl :: Maybe Bool
  }
  deriving (Int -> RoomEventFilter -> ShowS
[RoomEventFilter] -> ShowS
RoomEventFilter -> String
(Int -> RoomEventFilter -> ShowS)
-> (RoomEventFilter -> String)
-> ([RoomEventFilter] -> ShowS)
-> Show RoomEventFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoomEventFilter] -> ShowS
$cshowList :: [RoomEventFilter] -> ShowS
show :: RoomEventFilter -> String
$cshow :: RoomEventFilter -> String
showsPrec :: Int -> RoomEventFilter -> ShowS
$cshowsPrec :: Int -> RoomEventFilter -> ShowS
Show, RoomEventFilter -> RoomEventFilter -> Bool
(RoomEventFilter -> RoomEventFilter -> Bool)
-> (RoomEventFilter -> RoomEventFilter -> Bool)
-> Eq RoomEventFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoomEventFilter -> RoomEventFilter -> Bool
$c/= :: RoomEventFilter -> RoomEventFilter -> Bool
== :: RoomEventFilter -> RoomEventFilter -> Bool
$c== :: RoomEventFilter -> RoomEventFilter -> Bool
Eq, (forall x. RoomEventFilter -> Rep RoomEventFilter x)
-> (forall x. Rep RoomEventFilter x -> RoomEventFilter)
-> Generic RoomEventFilter
forall x. Rep RoomEventFilter x -> RoomEventFilter
forall x. RoomEventFilter -> Rep RoomEventFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RoomEventFilter x -> RoomEventFilter
$cfrom :: forall x. RoomEventFilter -> Rep RoomEventFilter x
Generic)

defaultRoomEventFilter :: RoomEventFilter
defaultRoomEventFilter :: RoomEventFilter
defaultRoomEventFilter = Maybe Int
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe Bool
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> RoomEventFilter
RoomEventFilter Maybe Int
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing

-- | A filter that should match nothing
roomEventFilterAll :: RoomEventFilter
roomEventFilterAll :: RoomEventFilter
roomEventFilterAll = RoomEventFilter
defaultRoomEventFilter {refLimit :: Maybe Int
refLimit = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0, refNotTypes :: Maybe [Text]
refNotTypes = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
"*"]}

instance ToJSON RoomEventFilter where
  toJSON :: RoomEventFilter -> Value
toJSON = Options -> RoomEventFilter -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON RoomEventFilter where
  parseJSON :: Value -> Parser RoomEventFilter
parseJSON = Options -> Value -> Parser RoomEventFilter
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

data StateFilter = StateFilter
  { StateFilter -> Maybe Int
sfLimit :: Maybe Int,
    StateFilter -> Maybe [Text]
sfNotSenders :: Maybe [T.Text],
    StateFilter -> Maybe [Text]
sfNotTypes :: Maybe [T.Text],
    StateFilter -> Maybe [Text]
sfSenders :: Maybe [T.Text],
    StateFilter -> Maybe [Text]
sfTypes :: Maybe [T.Text],
    StateFilter -> Maybe Bool
sfLazyLoadMembers :: Maybe Bool,
    StateFilter -> Maybe Bool
sfIncludeRedundantMembers :: Maybe Bool,
    StateFilter -> Maybe [Text]
sfNotRooms :: Maybe [T.Text],
    StateFilter -> Maybe [Text]
sfRooms :: Maybe [T.Text],
    StateFilter -> Maybe Bool
sfContains_url :: Maybe Bool
  }
  deriving (Int -> StateFilter -> ShowS
[StateFilter] -> ShowS
StateFilter -> String
(Int -> StateFilter -> ShowS)
-> (StateFilter -> String)
-> ([StateFilter] -> ShowS)
-> Show StateFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StateFilter] -> ShowS
$cshowList :: [StateFilter] -> ShowS
show :: StateFilter -> String
$cshow :: StateFilter -> String
showsPrec :: Int -> StateFilter -> ShowS
$cshowsPrec :: Int -> StateFilter -> ShowS
Show, StateFilter -> StateFilter -> Bool
(StateFilter -> StateFilter -> Bool)
-> (StateFilter -> StateFilter -> Bool) -> Eq StateFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StateFilter -> StateFilter -> Bool
$c/= :: StateFilter -> StateFilter -> Bool
== :: StateFilter -> StateFilter -> Bool
$c== :: StateFilter -> StateFilter -> Bool
Eq, (forall x. StateFilter -> Rep StateFilter x)
-> (forall x. Rep StateFilter x -> StateFilter)
-> Generic StateFilter
forall x. Rep StateFilter x -> StateFilter
forall x. StateFilter -> Rep StateFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StateFilter x -> StateFilter
$cfrom :: forall x. StateFilter -> Rep StateFilter x
Generic)

defaultStateFilter :: StateFilter
defaultStateFilter :: StateFilter
defaultStateFilter = Maybe Int
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> Maybe Bool
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Bool
-> StateFilter
StateFilter Maybe Int
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing

stateFilterAll :: StateFilter
stateFilterAll :: StateFilter
stateFilterAll = StateFilter
defaultStateFilter {sfLimit :: Maybe Int
sfLimit = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0, sfNotTypes :: Maybe [Text]
sfNotTypes = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
"*"]}

instance ToJSON StateFilter where
  toJSON :: StateFilter -> Value
toJSON = Options -> StateFilter -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON StateFilter where
  parseJSON :: Value -> Parser StateFilter
parseJSON = Options -> Value -> Parser StateFilter
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

data RoomFilter = RoomFilter
  { RoomFilter -> Maybe [Text]
rfNotRooms :: Maybe [T.Text],
    RoomFilter -> Maybe [Text]
rfRooms :: Maybe [T.Text],
    RoomFilter -> Maybe RoomEventFilter
rfEphemeral :: Maybe RoomEventFilter,
    RoomFilter -> Maybe Bool
rfIncludeLeave :: Maybe Bool,
    RoomFilter -> Maybe StateFilter
rfState :: Maybe StateFilter,
    RoomFilter -> Maybe RoomEventFilter
rfTimeline :: Maybe RoomEventFilter,
    RoomFilter -> Maybe RoomEventFilter
rfAccountData :: Maybe RoomEventFilter
  }
  deriving (Int -> RoomFilter -> ShowS
[RoomFilter] -> ShowS
RoomFilter -> String
(Int -> RoomFilter -> ShowS)
-> (RoomFilter -> String)
-> ([RoomFilter] -> ShowS)
-> Show RoomFilter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoomFilter] -> ShowS
$cshowList :: [RoomFilter] -> ShowS
show :: RoomFilter -> String
$cshow :: RoomFilter -> String
showsPrec :: Int -> RoomFilter -> ShowS
$cshowsPrec :: Int -> RoomFilter -> ShowS
Show, RoomFilter -> RoomFilter -> Bool
(RoomFilter -> RoomFilter -> Bool)
-> (RoomFilter -> RoomFilter -> Bool) -> Eq RoomFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoomFilter -> RoomFilter -> Bool
$c/= :: RoomFilter -> RoomFilter -> Bool
== :: RoomFilter -> RoomFilter -> Bool
$c== :: RoomFilter -> RoomFilter -> Bool
Eq, (forall x. RoomFilter -> Rep RoomFilter x)
-> (forall x. Rep RoomFilter x -> RoomFilter) -> Generic RoomFilter
forall x. Rep RoomFilter x -> RoomFilter
forall x. RoomFilter -> Rep RoomFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RoomFilter x -> RoomFilter
$cfrom :: forall x. RoomFilter -> Rep RoomFilter x
Generic)

defaultRoomFilter :: RoomFilter
defaultRoomFilter :: RoomFilter
defaultRoomFilter = Maybe [Text]
-> Maybe [Text]
-> Maybe RoomEventFilter
-> Maybe Bool
-> Maybe StateFilter
-> Maybe RoomEventFilter
-> Maybe RoomEventFilter
-> RoomFilter
RoomFilter Maybe [Text]
forall a. Maybe a
Nothing Maybe [Text]
forall a. Maybe a
Nothing Maybe RoomEventFilter
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe StateFilter
forall a. Maybe a
Nothing Maybe RoomEventFilter
forall a. Maybe a
Nothing Maybe RoomEventFilter
forall a. Maybe a
Nothing

instance ToJSON RoomFilter where
  toJSON :: RoomFilter -> Value
toJSON = Options -> RoomFilter -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON RoomFilter where
  parseJSON :: Value -> Parser RoomFilter
parseJSON = Options -> Value -> Parser RoomFilter
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

data Filter = Filter
  { Filter -> Maybe [Text]
filterEventFields :: Maybe [T.Text],
    Filter -> Maybe EventFormat
filterEventFormat :: Maybe EventFormat,
    Filter -> Maybe EventFilter
filterPresence :: Maybe EventFilter,
    Filter -> Maybe EventFilter
filterAccountData :: Maybe EventFilter,
    Filter -> Maybe RoomFilter
filterRoom :: Maybe RoomFilter
  }
  deriving (Int -> Filter -> ShowS
[Filter] -> ShowS
Filter -> String
(Int -> Filter -> ShowS)
-> (Filter -> String) -> ([Filter] -> ShowS) -> Show Filter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Filter] -> ShowS
$cshowList :: [Filter] -> ShowS
show :: Filter -> String
$cshow :: Filter -> String
showsPrec :: Int -> Filter -> ShowS
$cshowsPrec :: Int -> Filter -> ShowS
Show, Filter -> Filter -> Bool
(Filter -> Filter -> Bool)
-> (Filter -> Filter -> Bool) -> Eq Filter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Filter -> Filter -> Bool
$c/= :: Filter -> Filter -> Bool
== :: Filter -> Filter -> Bool
$c== :: Filter -> Filter -> Bool
Eq, (forall x. Filter -> Rep Filter x)
-> (forall x. Rep Filter x -> Filter) -> Generic Filter
forall x. Rep Filter x -> Filter
forall x. Filter -> Rep Filter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Filter x -> Filter
$cfrom :: forall x. Filter -> Rep Filter x
Generic)

defaultFilter :: Filter
defaultFilter :: Filter
defaultFilter = Maybe [Text]
-> Maybe EventFormat
-> Maybe EventFilter
-> Maybe EventFilter
-> Maybe RoomFilter
-> Filter
Filter Maybe [Text]
forall a. Maybe a
Nothing Maybe EventFormat
forall a. Maybe a
Nothing Maybe EventFilter
forall a. Maybe a
Nothing Maybe EventFilter
forall a. Maybe a
Nothing Maybe RoomFilter
forall a. Maybe a
Nothing

-- | A filter to keep all the messages
messageFilter :: Filter
messageFilter :: Filter
messageFilter =
  Filter
defaultFilter
    { filterPresence :: Maybe EventFilter
filterPresence = EventFilter -> Maybe EventFilter
forall a. a -> Maybe a
Just EventFilter
eventFilterAll,
      filterAccountData :: Maybe EventFilter
filterAccountData = EventFilter -> Maybe EventFilter
forall a. a -> Maybe a
Just EventFilter
eventFilterAll,
      filterRoom :: Maybe RoomFilter
filterRoom = RoomFilter -> Maybe RoomFilter
forall a. a -> Maybe a
Just RoomFilter
roomFilter
    }
  where
    roomFilter :: RoomFilter
roomFilter =
      RoomFilter
defaultRoomFilter
        { rfEphemeral :: Maybe RoomEventFilter
rfEphemeral = RoomEventFilter -> Maybe RoomEventFilter
forall a. a -> Maybe a
Just RoomEventFilter
roomEventFilterAll,
          rfState :: Maybe StateFilter
rfState = StateFilter -> Maybe StateFilter
forall a. a -> Maybe a
Just StateFilter
stateFilterAll,
          rfTimeline :: Maybe RoomEventFilter
rfTimeline = RoomEventFilter -> Maybe RoomEventFilter
forall a. a -> Maybe a
Just RoomEventFilter
timelineFilter,
          rfAccountData :: Maybe RoomEventFilter
rfAccountData = RoomEventFilter -> Maybe RoomEventFilter
forall a. a -> Maybe a
Just RoomEventFilter
roomEventFilterAll
        }
    timelineFilter :: RoomEventFilter
timelineFilter =
      RoomEventFilter
defaultRoomEventFilter
        { refTypes :: Maybe [Text]
refTypes = [Text] -> Maybe [Text]
forall a. a -> Maybe a
Just [Text
"m.room.message"]
        }

instance ToJSON Filter where
  toJSON :: Filter -> Value
toJSON = Options -> Filter -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON Filter where
  parseJSON :: Value -> Parser Filter
parseJSON = Options -> Value -> Parser Filter
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

-- | Upload a new filter definition to the homeserver
-- https://matrix.org/docs/spec/client_server/latest#post-matrix-client-r0-user-userid-filter
createFilter ::
  -- | The client session, use 'createSession' to get one.
  ClientSession ->
  -- | The userID, use 'getTokenOwner' to get it.
  UserID ->
  -- | The filter definition, use 'defaultFilter' to create one or use the 'messageFilter' example.
  Filter ->
  -- | The function returns a 'FilterID' suitable for the 'sync' function.
  MatrixIO FilterID
createFilter :: ClientSession -> UserID -> Filter -> MatrixIO FilterID
createFilter ClientSession
session (UserID Text
userID) Filter
body = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
path
  ClientSession -> Request -> MatrixIO FilterID
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest
    ClientSession
session
    ( Request
request
        { method :: ByteString
HTTP.method = ByteString
"POST",
          requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ Filter -> ByteString
forall a. ToJSON a => a -> ByteString
encode Filter
body
        }
    )
  where
    path :: Text
path = Text
"/_matrix/client/r0/user/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
userID Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/filter"

getFilter :: ClientSession -> UserID -> FilterID -> MatrixIO Filter
getFilter :: ClientSession -> UserID -> FilterID -> MatrixIO Filter
getFilter ClientSession
session (UserID Text
userID) (FilterID Text
filterID) =
  ClientSession -> Request -> MatrixIO Filter
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> MatrixIO Filter) -> IO Request -> MatrixIO Filter
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
path
  where
    path :: Text
path = Text
"/_matrix/client/r0/user/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
userID Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/filter/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
filterID

-------------------------------------------------------------------------------
-- https://matrix.org/docs/spec/client_server/latest#get-matrix-client-r0-sync
newtype Author = Author {Author -> Text
unAuthor :: T.Text}
  deriving (Int -> Author -> ShowS
[Author] -> ShowS
Author -> String
(Int -> Author -> ShowS)
-> (Author -> String) -> ([Author] -> ShowS) -> Show Author
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Author] -> ShowS
$cshowList :: [Author] -> ShowS
show :: Author -> String
$cshow :: Author -> String
showsPrec :: Int -> Author -> ShowS
$cshowsPrec :: Int -> Author -> ShowS
Show, Author -> Author -> Bool
(Author -> Author -> Bool)
-> (Author -> Author -> Bool) -> Eq Author
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Author -> Author -> Bool
$c/= :: Author -> Author -> Bool
== :: Author -> Author -> Bool
$c== :: Author -> Author -> Bool
Eq)
  deriving newtype (Value -> Parser [Author]
Value -> Parser Author
(Value -> Parser Author)
-> (Value -> Parser [Author]) -> FromJSON Author
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Author]
$cparseJSONList :: Value -> Parser [Author]
parseJSON :: Value -> Parser Author
$cparseJSON :: Value -> Parser Author
FromJSON, [Author] -> Encoding
[Author] -> Value
Author -> Encoding
Author -> Value
(Author -> Value)
-> (Author -> Encoding)
-> ([Author] -> Value)
-> ([Author] -> Encoding)
-> ToJSON Author
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Author] -> Encoding
$ctoEncodingList :: [Author] -> Encoding
toJSONList :: [Author] -> Value
$ctoJSONList :: [Author] -> Value
toEncoding :: Author -> Encoding
$ctoEncoding :: Author -> Encoding
toJSON :: Author -> Value
$ctoJSON :: Author -> Value
ToJSON)

data RoomEvent = RoomEvent
  { RoomEvent -> Event
reContent :: Event,
    RoomEvent -> Text
reType :: T.Text,
    RoomEvent -> EventID
reEventId :: EventID,
    RoomEvent -> Author
reSender :: Author
  }
  deriving (Int -> RoomEvent -> ShowS
[RoomEvent] -> ShowS
RoomEvent -> String
(Int -> RoomEvent -> ShowS)
-> (RoomEvent -> String)
-> ([RoomEvent] -> ShowS)
-> Show RoomEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoomEvent] -> ShowS
$cshowList :: [RoomEvent] -> ShowS
show :: RoomEvent -> String
$cshow :: RoomEvent -> String
showsPrec :: Int -> RoomEvent -> ShowS
$cshowsPrec :: Int -> RoomEvent -> ShowS
Show, RoomEvent -> RoomEvent -> Bool
(RoomEvent -> RoomEvent -> Bool)
-> (RoomEvent -> RoomEvent -> Bool) -> Eq RoomEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoomEvent -> RoomEvent -> Bool
$c/= :: RoomEvent -> RoomEvent -> Bool
== :: RoomEvent -> RoomEvent -> Bool
$c== :: RoomEvent -> RoomEvent -> Bool
Eq, (forall x. RoomEvent -> Rep RoomEvent x)
-> (forall x. Rep RoomEvent x -> RoomEvent) -> Generic RoomEvent
forall x. Rep RoomEvent x -> RoomEvent
forall x. RoomEvent -> Rep RoomEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RoomEvent x -> RoomEvent
$cfrom :: forall x. RoomEvent -> Rep RoomEvent x
Generic)

data RoomSummary = RoomSummary
  { RoomSummary -> Maybe Int
rsJoinedMemberCount :: Maybe Int,
    RoomSummary -> Maybe Int
rsInvitedMemberCount :: Maybe Int
  }
  deriving (Int -> RoomSummary -> ShowS
[RoomSummary] -> ShowS
RoomSummary -> String
(Int -> RoomSummary -> ShowS)
-> (RoomSummary -> String)
-> ([RoomSummary] -> ShowS)
-> Show RoomSummary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RoomSummary] -> ShowS
$cshowList :: [RoomSummary] -> ShowS
show :: RoomSummary -> String
$cshow :: RoomSummary -> String
showsPrec :: Int -> RoomSummary -> ShowS
$cshowsPrec :: Int -> RoomSummary -> ShowS
Show, RoomSummary -> RoomSummary -> Bool
(RoomSummary -> RoomSummary -> Bool)
-> (RoomSummary -> RoomSummary -> Bool) -> Eq RoomSummary
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RoomSummary -> RoomSummary -> Bool
$c/= :: RoomSummary -> RoomSummary -> Bool
== :: RoomSummary -> RoomSummary -> Bool
$c== :: RoomSummary -> RoomSummary -> Bool
Eq, (forall x. RoomSummary -> Rep RoomSummary x)
-> (forall x. Rep RoomSummary x -> RoomSummary)
-> Generic RoomSummary
forall x. Rep RoomSummary x -> RoomSummary
forall x. RoomSummary -> Rep RoomSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RoomSummary x -> RoomSummary
$cfrom :: forall x. RoomSummary -> Rep RoomSummary x
Generic)

data TimelineSync = TimelineSync
  { TimelineSync -> Maybe [RoomEvent]
tsEvents :: Maybe [RoomEvent],
    TimelineSync -> Maybe Bool
tsLimited :: Maybe Bool,
    TimelineSync -> Maybe Text
tsPrevBatch :: Maybe T.Text
  }
  deriving (Int -> TimelineSync -> ShowS
[TimelineSync] -> ShowS
TimelineSync -> String
(Int -> TimelineSync -> ShowS)
-> (TimelineSync -> String)
-> ([TimelineSync] -> ShowS)
-> Show TimelineSync
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimelineSync] -> ShowS
$cshowList :: [TimelineSync] -> ShowS
show :: TimelineSync -> String
$cshow :: TimelineSync -> String
showsPrec :: Int -> TimelineSync -> ShowS
$cshowsPrec :: Int -> TimelineSync -> ShowS
Show, TimelineSync -> TimelineSync -> Bool
(TimelineSync -> TimelineSync -> Bool)
-> (TimelineSync -> TimelineSync -> Bool) -> Eq TimelineSync
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimelineSync -> TimelineSync -> Bool
$c/= :: TimelineSync -> TimelineSync -> Bool
== :: TimelineSync -> TimelineSync -> Bool
$c== :: TimelineSync -> TimelineSync -> Bool
Eq, (forall x. TimelineSync -> Rep TimelineSync x)
-> (forall x. Rep TimelineSync x -> TimelineSync)
-> Generic TimelineSync
forall x. Rep TimelineSync x -> TimelineSync
forall x. TimelineSync -> Rep TimelineSync x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TimelineSync x -> TimelineSync
$cfrom :: forall x. TimelineSync -> Rep TimelineSync x
Generic)

data JoinedRoomSync = JoinedRoomSync
  { JoinedRoomSync -> Maybe RoomSummary
jrsSummary :: Maybe RoomSummary,
    JoinedRoomSync -> TimelineSync
jrsTimeline :: TimelineSync
  }
  deriving (Int -> JoinedRoomSync -> ShowS
[JoinedRoomSync] -> ShowS
JoinedRoomSync -> String
(Int -> JoinedRoomSync -> ShowS)
-> (JoinedRoomSync -> String)
-> ([JoinedRoomSync] -> ShowS)
-> Show JoinedRoomSync
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinedRoomSync] -> ShowS
$cshowList :: [JoinedRoomSync] -> ShowS
show :: JoinedRoomSync -> String
$cshow :: JoinedRoomSync -> String
showsPrec :: Int -> JoinedRoomSync -> ShowS
$cshowsPrec :: Int -> JoinedRoomSync -> ShowS
Show, JoinedRoomSync -> JoinedRoomSync -> Bool
(JoinedRoomSync -> JoinedRoomSync -> Bool)
-> (JoinedRoomSync -> JoinedRoomSync -> Bool) -> Eq JoinedRoomSync
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinedRoomSync -> JoinedRoomSync -> Bool
$c/= :: JoinedRoomSync -> JoinedRoomSync -> Bool
== :: JoinedRoomSync -> JoinedRoomSync -> Bool
$c== :: JoinedRoomSync -> JoinedRoomSync -> Bool
Eq, (forall x. JoinedRoomSync -> Rep JoinedRoomSync x)
-> (forall x. Rep JoinedRoomSync x -> JoinedRoomSync)
-> Generic JoinedRoomSync
forall x. Rep JoinedRoomSync x -> JoinedRoomSync
forall x. JoinedRoomSync -> Rep JoinedRoomSync x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinedRoomSync x -> JoinedRoomSync
$cfrom :: forall x. JoinedRoomSync -> Rep JoinedRoomSync x
Generic)

data Presence = Offline | Online | Unavailable deriving (Presence -> Presence -> Bool
(Presence -> Presence -> Bool)
-> (Presence -> Presence -> Bool) -> Eq Presence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Presence -> Presence -> Bool
$c/= :: Presence -> Presence -> Bool
== :: Presence -> Presence -> Bool
$c== :: Presence -> Presence -> Bool
Eq)

instance Show Presence where
  show :: Presence -> String
show = \case
    Presence
Offline -> String
"offline"
    Presence
Online -> String
"online"
    Presence
Unavailable -> String
"unavailable"

instance ToJSON Presence where
  toJSON :: Presence -> Value
toJSON Presence
ef = Text -> Value
String (Text -> Value) -> (Presence -> Text) -> Presence -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Presence -> Text
forall a. Show a => a -> Text
tshow (Presence -> Value) -> Presence -> Value
forall a b. (a -> b) -> a -> b
$ Presence
ef

instance FromJSON Presence where
  parseJSON :: Value -> Parser Presence
parseJSON Value
v = case Value
v of
    (String Text
"offline") -> Presence -> Parser Presence
forall (f :: * -> *) a. Applicative f => a -> f a
pure Presence
Offline
    (String Text
"online") -> Presence -> Parser Presence
forall (f :: * -> *) a. Applicative f => a -> f a
pure Presence
Online
    (String Text
"unavailable") -> Presence -> Parser Presence
forall (f :: * -> *) a. Applicative f => a -> f a
pure Presence
Unavailable
    Value
_ -> Parser Presence
forall (m :: * -> *) a. MonadPlus m => m a
mzero

data SyncResult = SyncResult
  { SyncResult -> Text
srNextBatch :: T.Text,
    SyncResult -> Maybe SyncResultRoom
srRooms :: Maybe SyncResultRoom
  }
  deriving (Int -> SyncResult -> ShowS
[SyncResult] -> ShowS
SyncResult -> String
(Int -> SyncResult -> ShowS)
-> (SyncResult -> String)
-> ([SyncResult] -> ShowS)
-> Show SyncResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SyncResult] -> ShowS
$cshowList :: [SyncResult] -> ShowS
show :: SyncResult -> String
$cshow :: SyncResult -> String
showsPrec :: Int -> SyncResult -> ShowS
$cshowsPrec :: Int -> SyncResult -> ShowS
Show, SyncResult -> SyncResult -> Bool
(SyncResult -> SyncResult -> Bool)
-> (SyncResult -> SyncResult -> Bool) -> Eq SyncResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SyncResult -> SyncResult -> Bool
$c/= :: SyncResult -> SyncResult -> Bool
== :: SyncResult -> SyncResult -> Bool
$c== :: SyncResult -> SyncResult -> Bool
Eq, (forall x. SyncResult -> Rep SyncResult x)
-> (forall x. Rep SyncResult x -> SyncResult) -> Generic SyncResult
forall x. Rep SyncResult x -> SyncResult
forall x. SyncResult -> Rep SyncResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SyncResult x -> SyncResult
$cfrom :: forall x. SyncResult -> Rep SyncResult x
Generic)

data SyncResultRoom = SyncResultRoom
  { SyncResultRoom -> Maybe (Map Text JoinedRoomSync)
srrJoin :: Maybe (Map T.Text JoinedRoomSync)
  , SyncResultRoom -> Maybe (Map Text InvitedRoomSync)
srrInvite :: Maybe (Map T.Text InvitedRoomSync)
  }
  deriving (Int -> SyncResultRoom -> ShowS
[SyncResultRoom] -> ShowS
SyncResultRoom -> String
(Int -> SyncResultRoom -> ShowS)
-> (SyncResultRoom -> String)
-> ([SyncResultRoom] -> ShowS)
-> Show SyncResultRoom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SyncResultRoom] -> ShowS
$cshowList :: [SyncResultRoom] -> ShowS
show :: SyncResultRoom -> String
$cshow :: SyncResultRoom -> String
showsPrec :: Int -> SyncResultRoom -> ShowS
$cshowsPrec :: Int -> SyncResultRoom -> ShowS
Show, SyncResultRoom -> SyncResultRoom -> Bool
(SyncResultRoom -> SyncResultRoom -> Bool)
-> (SyncResultRoom -> SyncResultRoom -> Bool) -> Eq SyncResultRoom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SyncResultRoom -> SyncResultRoom -> Bool
$c/= :: SyncResultRoom -> SyncResultRoom -> Bool
== :: SyncResultRoom -> SyncResultRoom -> Bool
$c== :: SyncResultRoom -> SyncResultRoom -> Bool
Eq, (forall x. SyncResultRoom -> Rep SyncResultRoom x)
-> (forall x. Rep SyncResultRoom x -> SyncResultRoom)
-> Generic SyncResultRoom
forall x. Rep SyncResultRoom x -> SyncResultRoom
forall x. SyncResultRoom -> Rep SyncResultRoom x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SyncResultRoom x -> SyncResultRoom
$cfrom :: forall x. SyncResultRoom -> Rep SyncResultRoom x
Generic)

data InvitedRoomSync = InvitedRoomSync
  deriving (Int -> InvitedRoomSync -> ShowS
[InvitedRoomSync] -> ShowS
InvitedRoomSync -> String
(Int -> InvitedRoomSync -> ShowS)
-> (InvitedRoomSync -> String)
-> ([InvitedRoomSync] -> ShowS)
-> Show InvitedRoomSync
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InvitedRoomSync] -> ShowS
$cshowList :: [InvitedRoomSync] -> ShowS
show :: InvitedRoomSync -> String
$cshow :: InvitedRoomSync -> String
showsPrec :: Int -> InvitedRoomSync -> ShowS
$cshowsPrec :: Int -> InvitedRoomSync -> ShowS
Show, InvitedRoomSync -> InvitedRoomSync -> Bool
(InvitedRoomSync -> InvitedRoomSync -> Bool)
-> (InvitedRoomSync -> InvitedRoomSync -> Bool)
-> Eq InvitedRoomSync
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InvitedRoomSync -> InvitedRoomSync -> Bool
$c/= :: InvitedRoomSync -> InvitedRoomSync -> Bool
== :: InvitedRoomSync -> InvitedRoomSync -> Bool
$c== :: InvitedRoomSync -> InvitedRoomSync -> Bool
Eq, (forall x. InvitedRoomSync -> Rep InvitedRoomSync x)
-> (forall x. Rep InvitedRoomSync x -> InvitedRoomSync)
-> Generic InvitedRoomSync
forall x. Rep InvitedRoomSync x -> InvitedRoomSync
forall x. InvitedRoomSync -> Rep InvitedRoomSync x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InvitedRoomSync x -> InvitedRoomSync
$cfrom :: forall x. InvitedRoomSync -> Rep InvitedRoomSync x
Generic)

unFilterID :: FilterID -> T.Text
unFilterID :: FilterID -> Text
unFilterID (FilterID Text
x) = Text
x

-------------------------------------------------------------------------------
-- https://matrix.org/docs/spec/client_server/latest#forming-relationships-between-events

-- | An helper to create a reply body
--
-- >>> let sender = Author "foo@matrix.org"
-- >>> addReplyBody sender "Hello" "hi"
-- "> <foo@matrix.org> Hello\n\nhi"
--
-- >>> addReplyBody sender "" "hey"
-- "> <foo@matrix.org>\n\nhey"
--
-- >>> addReplyBody sender "a multi\nline" "resp"
-- "> <foo@matrix.org> a multi\n> line\n\nresp"
addReplyBody :: Author -> T.Text -> T.Text -> T.Text
addReplyBody :: Author -> Text -> Text -> Text
addReplyBody (Author Text
author) Text
old Text
reply =
  let oldLines :: [Text]
oldLines = Text -> [Text]
T.lines Text
old
      headLine :: Text
headLine = Text
"> <" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
author Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> (Text -> Text) -> Maybe Text -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" (Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend Text
" ") ([Text] -> Maybe Text
forall a. [a] -> Maybe a
headMaybe [Text]
oldLines)
      newBody :: [Text]
newBody = [Text
headLine] [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text -> Text
forall a. Monoid a => a -> a -> a
mappend Text
"> ") ([Text] -> [Text]
forall a. [a] -> [a]
tail' [Text]
oldLines) [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
""] [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
reply]
   in Int -> Text -> Text
T.dropEnd Int
1 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.unlines [Text]
newBody

addReplyFormattedBody :: RoomID -> EventID -> Author -> T.Text -> T.Text -> T.Text
addReplyFormattedBody :: RoomID -> EventID -> Author -> Text -> Text -> Text
addReplyFormattedBody (RoomID Text
roomID) (EventID Text
eventID) (Author Text
author) Text
old Text
reply =
  [Text] -> Text
T.unlines
    [ Text
"<mx-reply>",
      Text
"  <blockquote>",
      Text
"    <a href=\"https://matrix.to/#/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
roomID Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eventID Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\">In reply to</a>",
      Text
"    <a href=\"https://matrix.to/#/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
author Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
author Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</a>",
      Text
"    <br />",
      Text
"    " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
old,
      Text
"  </blockquote>",
      Text
"</mx-reply>",
      Text
reply
    ]

-- | Convert body by encoding HTML special char
--
-- >>> toFormattedBody "& <test>"
-- "&amp; &lt;test&gt;"
toFormattedBody :: T.Text -> T.Text
toFormattedBody :: Text -> Text
toFormattedBody = (Char -> Text) -> Text -> Text
T.concatMap Char -> Text
char
  where
    char :: Char -> Text
char Char
x = case Char
x of
      Char
'<' -> Text
"&lt;"
      Char
'>' -> Text
"&gt;"
      Char
'&' -> Text
"&amp;"
      Char
_ -> Char -> Text
T.singleton Char
x

-- | Prepare a reply event
mkReply ::
  -- | The destination room, must match the original event
  RoomID ->
  -- | The original event
  RoomEvent ->
  -- | The reply message
  MessageText ->
  -- | The event to send
  Event
mkReply :: RoomID -> RoomEvent -> MessageText -> Event
mkReply RoomID
room RoomEvent
re MessageText
mt =
  let getFormattedBody :: MessageText -> Text
getFormattedBody MessageText
mt' = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (Text -> Text
toFormattedBody (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageText -> Text
mtBody MessageText
mt') (MessageText -> Maybe Text
mtFormattedBody MessageText
mt')
      eventID :: EventID
eventID = RoomEvent -> EventID
reEventId RoomEvent
re
      author :: Author
author = RoomEvent -> Author
reSender RoomEvent
re
      updateText :: MessageText -> MessageText
updateText MessageText
oldMT =
        MessageText
oldMT
          { mtFormat :: Maybe Text
mtFormat = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"org.matrix.custom.html",
            mtBody :: Text
mtBody = Author -> Text -> Text -> Text
addReplyBody Author
author (MessageText -> Text
mtBody MessageText
oldMT) (MessageText -> Text
mtBody MessageText
mt),
            mtFormattedBody :: Maybe Text
mtFormattedBody =
              Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$
                RoomID -> EventID -> Author -> Text -> Text -> Text
addReplyFormattedBody
                  RoomID
room
                  EventID
eventID
                  Author
author
                  (MessageText -> Text
getFormattedBody MessageText
oldMT)
                  (MessageText -> Text
getFormattedBody MessageText
mt)
          }

      newMessage :: MessageText
newMessage = case RoomEvent -> Event
reContent RoomEvent
re of
        EventRoomMessage (RoomMessageText MessageText
oldMT) -> MessageText -> MessageText
updateText MessageText
oldMT
        EventRoomReply EventID
_ (RoomMessageText MessageText
oldMT) -> MessageText -> MessageText
updateText MessageText
oldMT
        EventRoomEdit (EventID, RoomMessage)
_ (RoomMessageText MessageText
oldMT) -> MessageText -> MessageText
updateText MessageText
oldMT
        EventUnknown Object
x -> String -> MessageText
forall a. HasCallStack => String -> a
error (String -> MessageText) -> String -> MessageText
forall a b. (a -> b) -> a -> b
$ String
"Can't reply to " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Object -> String
forall a. Show a => a -> String
show Object
x
   in EventID -> RoomMessage -> Event
EventRoomReply EventID
eventID (MessageText -> RoomMessage
RoomMessageText MessageText
newMessage)

sync :: ClientSession -> Maybe FilterID -> Maybe T.Text -> Maybe Presence -> Maybe Int -> MatrixIO SyncResult
sync :: ClientSession
-> Maybe FilterID
-> Maybe Text
-> Maybe Presence
-> Maybe Int
-> MatrixIO SyncResult
sync ClientSession
session Maybe FilterID
filterM Maybe Text
sinceM Maybe Presence
presenceM Maybe Int
timeoutM = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True Text
"/_matrix/client/r0/sync"
  ClientSession -> Request -> MatrixIO SyncResult
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session ([(ByteString, Maybe ByteString)] -> Request -> Request
HTTP.setQueryString [(ByteString, Maybe ByteString)]
qs Request
request)
  where
    toQs :: a -> Maybe Text -> [(a, Maybe ByteString)]
toQs a
name = \case
      Maybe Text
Nothing -> []
      Just Text
v -> [(a
name, ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (Text -> ByteString) -> Text -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> Maybe ByteString) -> Text -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Text
v)]
    qs :: [(ByteString, Maybe ByteString)]
qs =
      ByteString -> Maybe Text -> [(ByteString, Maybe ByteString)]
forall a. a -> Maybe Text -> [(a, Maybe ByteString)]
toQs ByteString
"filter" (FilterID -> Text
unFilterID (FilterID -> Text) -> Maybe FilterID -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe FilterID
filterM)
        [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
forall a. Semigroup a => a -> a -> a
<> ByteString -> Maybe Text -> [(ByteString, Maybe ByteString)]
forall a. a -> Maybe Text -> [(a, Maybe ByteString)]
toQs ByteString
"since" Maybe Text
sinceM
        [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
forall a. Semigroup a => a -> a -> a
<> ByteString -> Maybe Text -> [(ByteString, Maybe ByteString)]
forall a. a -> Maybe Text -> [(a, Maybe ByteString)]
toQs ByteString
"set_presence" (Presence -> Text
forall a. Show a => a -> Text
tshow (Presence -> Text) -> Maybe Presence -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Presence
presenceM)
        [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
-> [(ByteString, Maybe ByteString)]
forall a. Semigroup a => a -> a -> a
<> ByteString -> Maybe Text -> [(ByteString, Maybe ByteString)]
forall a. a -> Maybe Text -> [(a, Maybe ByteString)]
toQs ByteString
"timeout" (Int -> Text
forall a. Show a => a -> Text
tshow (Int -> Text) -> Maybe Int -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Int
timeoutM)

syncPoll ::
  (MonadIO m) =>
  -- | The client session, use 'createSession' to get one.
  ClientSession ->
  -- | A sync filter, use 'createFilter' to get one.
  Maybe FilterID ->
  -- | A since value, get it from a previous sync result using the 'srNextBatch' field.
  Maybe T.Text ->
  -- | Set the session presence.
  Maybe Presence ->
  -- | Your callback to handle sync result.
  (SyncResult -> m ()) ->
  -- | This function does not return unless there is an error.
  MatrixM m ()
syncPoll :: ClientSession
-> Maybe FilterID
-> Maybe Text
-> Maybe Presence
-> (SyncResult -> m ())
-> MatrixM m ()
syncPoll ClientSession
session Maybe FilterID
filterM Maybe Text
sinceM Maybe Presence
presenceM SyncResult -> m ()
cb = Maybe Text -> MatrixM m ()
forall b. Maybe Text -> m (Either MatrixError b)
go Maybe Text
sinceM
  where
    go :: Maybe Text -> m (Either MatrixError b)
go Maybe Text
since = do
      Either MatrixError SyncResult
syncResultE <- MatrixIO SyncResult -> m (Either MatrixError SyncResult)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MatrixIO SyncResult -> m (Either MatrixError SyncResult))
-> MatrixIO SyncResult -> m (Either MatrixError SyncResult)
forall a b. (a -> b) -> a -> b
$ MatrixIO SyncResult -> MatrixIO SyncResult
forall (m :: * -> *) a.
(MonadIO m, MonadMask m) =>
MatrixM m a -> MatrixM m a
retry (MatrixIO SyncResult -> MatrixIO SyncResult)
-> MatrixIO SyncResult -> MatrixIO SyncResult
forall a b. (a -> b) -> a -> b
$ ClientSession
-> Maybe FilterID
-> Maybe Text
-> Maybe Presence
-> Maybe Int
-> MatrixIO SyncResult
sync ClientSession
session Maybe FilterID
filterM Maybe Text
since Maybe Presence
presenceM (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
10_000)
      case Either MatrixError SyncResult
syncResultE of
        Left MatrixError
err -> Either MatrixError b -> m (Either MatrixError b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MatrixError -> Either MatrixError b
forall a b. a -> Either a b
Left MatrixError
err)
        Right SyncResult
sr -> SyncResult -> m ()
cb SyncResult
sr m () -> m (Either MatrixError b) -> m (Either MatrixError b)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Maybe Text -> m (Either MatrixError b)
go (Text -> Maybe Text
forall a. a -> Maybe a
Just (SyncResult -> Text
srNextBatch SyncResult
sr))

-- | Extract room events from a sync result
getTimelines :: SyncResult -> [(RoomID, NonEmpty RoomEvent)]
getTimelines :: SyncResult -> [(RoomID, NonEmpty RoomEvent)]
getTimelines SyncResult
sr = (Text
 -> JoinedRoomSync
 -> [(RoomID, NonEmpty RoomEvent)]
 -> [(RoomID, NonEmpty RoomEvent)])
-> [(RoomID, NonEmpty RoomEvent)]
-> Map Text JoinedRoomSync
-> [(RoomID, NonEmpty RoomEvent)]
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey Text
-> JoinedRoomSync
-> [(RoomID, NonEmpty RoomEvent)]
-> [(RoomID, NonEmpty RoomEvent)]
getEvents [] Map Text JoinedRoomSync
joinedRooms
  where
    getEvents :: T.Text -> JoinedRoomSync -> [(RoomID, NonEmpty RoomEvent)] -> [(RoomID, NonEmpty RoomEvent)]
    getEvents :: Text
-> JoinedRoomSync
-> [(RoomID, NonEmpty RoomEvent)]
-> [(RoomID, NonEmpty RoomEvent)]
getEvents Text
roomID JoinedRoomSync
jrs [(RoomID, NonEmpty RoomEvent)]
acc = case TimelineSync -> Maybe [RoomEvent]
tsEvents (JoinedRoomSync -> TimelineSync
jrsTimeline JoinedRoomSync
jrs) of
      Just (RoomEvent
x : [RoomEvent]
xs) -> (Text -> RoomID
RoomID Text
roomID, RoomEvent
x RoomEvent -> [RoomEvent] -> NonEmpty RoomEvent
forall a. a -> [a] -> NonEmpty a
:| [RoomEvent]
xs) (RoomID, NonEmpty RoomEvent)
-> [(RoomID, NonEmpty RoomEvent)] -> [(RoomID, NonEmpty RoomEvent)]
forall a. a -> [a] -> [a]
: [(RoomID, NonEmpty RoomEvent)]
acc
      Maybe [RoomEvent]
_ -> [(RoomID, NonEmpty RoomEvent)]
acc
    joinedRooms :: Map Text JoinedRoomSync
joinedRooms = Map Text JoinedRoomSync
-> Maybe (Map Text JoinedRoomSync) -> Map Text JoinedRoomSync
forall a. a -> Maybe a -> a
fromMaybe Map Text JoinedRoomSync
forall a. Monoid a => a
mempty (Maybe (Map Text JoinedRoomSync) -> Map Text JoinedRoomSync)
-> Maybe (Map Text JoinedRoomSync) -> Map Text JoinedRoomSync
forall a b. (a -> b) -> a -> b
$ SyncResult -> Maybe SyncResultRoom
srRooms SyncResult
sr Maybe SyncResultRoom
-> (SyncResultRoom -> Maybe (Map Text JoinedRoomSync))
-> Maybe (Map Text JoinedRoomSync)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= SyncResultRoom -> Maybe (Map Text JoinedRoomSync)
srrJoin

-------------------------------------------------------------------------------
-- Derived JSON instances
instance ToJSON RoomEvent where
  toJSON :: RoomEvent -> Value
toJSON RoomEvent {Text
EventID
Event
Author
reSender :: Author
reEventId :: EventID
reType :: Text
reContent :: Event
reSender :: RoomEvent -> Author
reEventId :: RoomEvent -> EventID
reType :: RoomEvent -> Text
reContent :: RoomEvent -> Event
..} =
    [Pair] -> Value
object
      [ Key
"content" Key -> Event -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Event
reContent,
        Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
reType,
        Key
"event_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= EventID -> Text
unEventID EventID
reEventId,
        Key
"sender" Key -> Author -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Author
reSender
      ]

instance FromJSON RoomEvent where
  parseJSON :: Value -> Parser RoomEvent
parseJSON (Object Object
o) = do
    Text
eventId <- Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"event_id"
    Event -> Text -> EventID -> Author -> RoomEvent
RoomEvent (Event -> Text -> EventID -> Author -> RoomEvent)
-> Parser Event -> Parser (Text -> EventID -> Author -> RoomEvent)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser Event
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content" Parser (Text -> EventID -> Author -> RoomEvent)
-> Parser Text -> Parser (EventID -> Author -> RoomEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" Parser (EventID -> Author -> RoomEvent)
-> Parser EventID -> Parser (Author -> RoomEvent)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> EventID -> Parser EventID
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> EventID
EventID Text
eventId) Parser (Author -> RoomEvent) -> Parser Author -> Parser RoomEvent
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser Author
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"sender"
  parseJSON Value
_ = Parser RoomEvent
forall (m :: * -> *) a. MonadPlus m => m a
mzero

instance ToJSON RoomSummary where
  toJSON :: RoomSummary -> Value
toJSON = Options -> RoomSummary -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON RoomSummary where
  parseJSON :: Value -> Parser RoomSummary
parseJSON = Options -> Value -> Parser RoomSummary
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

instance ToJSON TimelineSync where
  toJSON :: TimelineSync -> Value
toJSON = Options -> TimelineSync -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON TimelineSync where
  parseJSON :: Value -> Parser TimelineSync
parseJSON = Options -> Value -> Parser TimelineSync
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

instance ToJSON JoinedRoomSync where
  toJSON :: JoinedRoomSync -> Value
toJSON = Options -> JoinedRoomSync -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON JoinedRoomSync where
  parseJSON :: Value -> Parser JoinedRoomSync
parseJSON = Options -> Value -> Parser JoinedRoomSync
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

instance ToJSON InvitedRoomSync where
  toJSON :: InvitedRoomSync -> Value
toJSON InvitedRoomSync
_ = [Pair] -> Value
object []

instance FromJSON InvitedRoomSync where
  parseJSON :: Value -> Parser InvitedRoomSync
parseJSON Value
_ = InvitedRoomSync -> Parser InvitedRoomSync
forall (f :: * -> *) a. Applicative f => a -> f a
pure InvitedRoomSync
InvitedRoomSync

instance ToJSON SyncResult where
  toJSON :: SyncResult -> Value
toJSON = Options -> SyncResult -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON SyncResult where
  parseJSON :: Value -> Parser SyncResult
parseJSON = Options -> Value -> Parser SyncResult
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

instance ToJSON SyncResultRoom where
  toJSON :: SyncResultRoom -> Value
toJSON = Options -> SyncResultRoom -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
genericToJSON Options
aesonOptions

instance FromJSON SyncResultRoom where
  parseJSON :: Value -> Parser SyncResultRoom
parseJSON = Options -> Value -> Parser SyncResultRoom
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
aesonOptions

getAccountData' :: (FromJSON a) => ClientSession -> UserID -> T.Text -> MatrixIO a
getAccountData' :: ClientSession -> UserID -> Text -> MatrixIO a
getAccountData' ClientSession
session UserID
userID Text
t =
  ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (UserID -> Text -> Text
accountDataPath UserID
userID Text
t) IO Request -> (Request -> MatrixIO a) -> MatrixIO a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ClientSession -> Request -> MatrixIO a
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session

setAccountData' :: (ToJSON a) => ClientSession -> UserID -> T.Text -> a -> MatrixIO ()
setAccountData' :: ClientSession -> UserID -> Text -> a -> MatrixIO ()
setAccountData' ClientSession
session UserID
userID Text
t a
value = do
  Request
request <- ClientSession -> Bool -> Text -> IO Request
mkRequest ClientSession
session Bool
True (Text -> IO Request) -> Text -> IO Request
forall a b. (a -> b) -> a -> b
$ UserID -> Text -> Text
accountDataPath UserID
userID Text
t
  Either MatrixError Object -> Either MatrixError ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Either MatrixError Object -> Either MatrixError ())
-> IO (Either MatrixError Object) -> MatrixIO ()
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ClientSession -> Request -> IO (Either MatrixError Object)
forall a. FromJSON a => ClientSession -> Request -> MatrixIO a
doRequest ClientSession
session (Request -> IO (Either MatrixError Object))
-> Request -> IO (Either MatrixError Object)
forall a b. (a -> b) -> a -> b
$ Request
request
             { method :: ByteString
HTTP.method = ByteString
"PUT"
             , requestBody :: RequestBody
HTTP.requestBody = ByteString -> RequestBody
HTTP.RequestBodyLBS (ByteString -> RequestBody) -> ByteString -> RequestBody
forall a b. (a -> b) -> a -> b
$ a -> ByteString
forall a. ToJSON a => a -> ByteString
encode a
value
             } :: MatrixIO Aeson.Object
           )

accountDataPath :: UserID -> T.Text -> T.Text
accountDataPath :: UserID -> Text -> Text
accountDataPath (UserID Text
userID) Text
t =
  Text
"/_matrix/client/r0/user/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
userID Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/account_data/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t

class (FromJSON a, ToJSON a) => AccountData a where
  accountDataType :: proxy a -> T.Text

getAccountData :: forall a. (AccountData a) => ClientSession -> UserID -> MatrixIO a
getAccountData :: ClientSession -> UserID -> MatrixIO a
getAccountData ClientSession
session UserID
userID = ClientSession -> UserID -> Text -> MatrixIO a
forall a.
FromJSON a =>
ClientSession -> UserID -> Text -> MatrixIO a
getAccountData' ClientSession
session UserID
userID (Text -> MatrixIO a) -> Text -> MatrixIO a
forall a b. (a -> b) -> a -> b
$
                                Proxy a -> Text
forall a (proxy :: * -> *). AccountData a => proxy a -> Text
accountDataType (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)

setAccountData :: forall a. (AccountData a) => ClientSession -> UserID -> a -> MatrixIO ()
setAccountData :: ClientSession -> UserID -> a -> MatrixIO ()
setAccountData ClientSession
session UserID
userID = ClientSession -> UserID -> Text -> a -> MatrixIO ()
forall a.
ToJSON a =>
ClientSession -> UserID -> Text -> a -> MatrixIO ()
setAccountData' ClientSession
session UserID
userID (Text -> a -> MatrixIO ()) -> Text -> a -> MatrixIO ()
forall a b. (a -> b) -> a -> b
$
                                Proxy a -> Text
forall a (proxy :: * -> *). AccountData a => proxy a -> Text
accountDataType (Proxy a
forall k (t :: k). Proxy t
Proxy :: Proxy a)

-------------------------------------------------------------------------------
-- Utils

headMaybe :: [a] -> Maybe a
headMaybe :: [a] -> Maybe a
headMaybe [a]
xs = case [a]
xs of
  [] -> Maybe a
forall a. Maybe a
Nothing
  (a
x : [a]
_) -> a -> Maybe a
forall a. a -> Maybe a
Just a
x

tail' :: [a] -> [a]
tail' :: [a] -> [a]
tail' [a]
xs = case [a]
xs of
  [] -> []
  (a
_ : [a]
rest) -> [a]
rest

indistinct :: Either x x -> x
indistinct :: Either x x -> x
indistinct = x -> x
forall a. a -> a
id (x -> x) -> (x -> x) -> Either x x -> x
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
`either` x -> x
forall a. a -> a
id

tshow :: Show a => a -> T.Text
tshow :: a -> Text
tshow = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show

escapeUriComponent :: T.Text -> T.Text
escapeUriComponent :: Text -> Text
escapeUriComponent = String -> Text
T.pack (String -> Text) -> (Text -> String) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> ShowS
URI.escapeURIString Char -> Bool
URI.isUnreserved ShowS -> (Text -> String) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack