Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Network.Matrix.Client
Description
This module contains the client-server API https://matrix.org/docs/spec/client_server/r0.6.1
Synopsis
- data ClientSession
- data LoginCredentials = LoginCredentials {}
- newtype MatrixToken = MatrixToken Text
- newtype Username = Username {}
- newtype DeviceId = DeviceId {}
- newtype InitialDeviceDisplayName = InitialDeviceDisplayName {}
- data LoginSecret
- data LoginResponse = LoginResponse {
- lrUserId :: Text
- lrAccessToken :: Text
- lrHomeServer :: Text
- lrDeviceId :: Text
- getTokenFromEnv :: Text -> IO MatrixToken
- createSession :: Text -> MatrixToken -> IO ClientSession
- login :: LoginCredentials -> IO ClientSession
- loginToken :: LoginCredentials -> IO (ClientSession, MatrixToken)
- logout :: ClientSession -> MatrixIO ()
- type MatrixM m a = m (Either MatrixError a)
- type MatrixIO a = MatrixM IO a
- data MatrixError = MatrixError {}
- retry :: (MonadIO m, MonadMask m) => MatrixM m a -> MatrixM m a
- retryWithLog :: (MonadMask m, MonadIO m) => Int -> (Text -> m ()) -> MatrixM m a -> MatrixM m a
- newtype UserID = UserID Text
- getTokenOwner :: ClientSession -> MatrixIO UserID
- data Dir
- newtype EventType = EventType Text
- data MRCreate = MRCreate {}
- newtype MRCanonicalAlias = MRCanonicalAlias {}
- newtype MRGuestAccess = MRGuestAccess {}
- newtype MRHistoryVisibility = MRHistoryVisibility {}
- newtype MRName = MRName {}
- newtype MRTopic = MRTopic {}
- data PaginatedRoomMessages = PaginatedRoomMessages {}
- newtype StateKey = StateKey Text
- data StateEvent = StateEvent {}
- data StateContent
- getRoomEvent :: ClientSession -> RoomID -> EventID -> MatrixIO RoomEvent
- getRoomMembers :: ClientSession -> RoomID -> MatrixIO (Map UserID User)
- getRoomState :: ClientSession -> RoomID -> MatrixIO [StateEvent]
- getRoomStateEvent :: ClientSession -> RoomID -> EventType -> StateKey -> MatrixIO StateEvent
- getRoomMessages :: ClientSession -> RoomID -> Dir -> Maybe RoomEventFilter -> Text -> Maybe Int -> Maybe Int -> MatrixIO PaginatedRoomMessages
- redact :: ClientSession -> RoomID -> EventID -> TxnID -> Text -> MatrixIO EventID
- sendRoomStateEvent :: ClientSession -> RoomID -> EventType -> StateKey -> Value -> MatrixIO EventID
- data RoomCreatePreset
- data RoomCreateRequest = RoomCreateRequest {}
- createRoom :: ClientSession -> RoomCreateRequest -> MatrixIO RoomID
- data ResolvedRoomAlias = ResolvedRoomAlias {}
- newtype TxnID = TxnID Text
- sendMessage :: ClientSession -> RoomID -> Event -> TxnID -> MatrixIO EventID
- mkReply :: RoomID -> RoomEvent -> MessageText -> Event
- data MessageTextType
- data MessageText = MessageText {
- mtBody :: Text
- mtType :: MessageTextType
- mtFormat :: Maybe Text
- mtFormattedBody :: Maybe Text
- newtype RoomMessage = RoomMessageText MessageText
- data Event
- newtype EventID = EventID {}
- eventType :: Event -> Text
- setRoomAlias :: ClientSession -> RoomAlias -> RoomID -> MatrixIO ()
- setRoomVisibility :: ClientSession -> RoomID -> Visibility -> MatrixIO ()
- resolveRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ResolvedRoomAlias
- deleteRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ()
- getRoomAliases :: ClientSession -> RoomID -> MatrixIO [RoomAlias]
- newtype RoomID = RoomID Text
- newtype RoomAlias = RoomAlias Text
- banUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
- checkRoomVisibility :: ClientSession -> RoomID -> MatrixIO Visibility
- forgetRoom :: ClientSession -> RoomID -> MatrixIO ()
- getJoinedRooms :: ClientSession -> MatrixIO [RoomID]
- getPublicRooms :: ClientSession -> Maybe Int -> Maybe PaginationChunk -> MatrixIO PublicRooms
- getPublicRooms' :: ClientSession -> Maybe Int -> Maybe PaginationChunk -> Maybe Text -> Maybe Bool -> Maybe ThirdPartyInstanceId -> MatrixIO PublicRooms
- inviteToRoom :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
- joinRoom :: ClientSession -> Text -> MatrixIO RoomID
- joinRoomById :: ClientSession -> RoomID -> MatrixIO RoomID
- leaveRoomById :: ClientSession -> RoomID -> MatrixIO ()
- kickUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
- knockOnRoom :: ClientSession -> Either RoomID RoomAlias -> [Text] -> Maybe Text -> MatrixIO RoomID
- unbanUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO ()
- data EventFormat
- = Client
- | Federation
- data EventFilter = EventFilter {}
- defaultEventFilter :: EventFilter
- eventFilterAll :: EventFilter
- data RoomEventFilter = RoomEventFilter {
- refLimit :: Maybe Int
- refNotSenders :: Maybe [Text]
- refNotTypes :: Maybe [Text]
- refSenders :: Maybe [Text]
- refTypes :: Maybe [Text]
- refLazyLoadMembers :: Maybe Bool
- refIncludeRedundantMembers :: Maybe Bool
- refNotRooms :: Maybe [Text]
- refRooms :: Maybe [Text]
- refContainsUrl :: Maybe Bool
- defaultRoomEventFilter :: RoomEventFilter
- roomEventFilterAll :: RoomEventFilter
- data StateFilter = StateFilter {
- sfLimit :: Maybe Int
- sfNotSenders :: Maybe [Text]
- sfNotTypes :: Maybe [Text]
- sfSenders :: Maybe [Text]
- sfTypes :: Maybe [Text]
- sfLazyLoadMembers :: Maybe Bool
- sfIncludeRedundantMembers :: Maybe Bool
- sfNotRooms :: Maybe [Text]
- sfRooms :: Maybe [Text]
- sfContains_url :: Maybe Bool
- defaultStateFilter :: StateFilter
- stateFilterAll :: StateFilter
- data RoomFilter = RoomFilter {}
- defaultRoomFilter :: RoomFilter
- data Filter = Filter {}
- defaultFilter :: Filter
- newtype FilterID = FilterID Text
- messageFilter :: Filter
- createFilter :: ClientSession -> UserID -> Filter -> MatrixIO FilterID
- getFilter :: ClientSession -> UserID -> FilterID -> MatrixIO Filter
- class (FromJSON a, ToJSON a) => AccountData a where
- accountDataType :: proxy a -> Text
- getAccountData :: forall a. AccountData a => ClientSession -> UserID -> MatrixIO a
- getAccountData' :: FromJSON a => ClientSession -> UserID -> Text -> MatrixIO a
- setAccountData :: forall a. AccountData a => ClientSession -> UserID -> a -> MatrixIO ()
- setAccountData' :: ToJSON a => ClientSession -> UserID -> Text -> a -> MatrixIO ()
- sync :: ClientSession -> Maybe FilterID -> Maybe Text -> Maybe Presence -> Maybe Int -> MatrixIO SyncResult
- getTimelines :: SyncResult -> [(RoomID, NonEmpty RoomEvent)]
- syncPoll :: MonadIO m => ClientSession -> Maybe FilterID -> Maybe Text -> Maybe Presence -> (SyncResult -> m ()) -> MatrixM m ()
- newtype Author = Author {}
- data Presence
- = Offline
- | Online
- | Unavailable
- data RoomEvent = RoomEvent {}
- data RoomSummary = RoomSummary {}
- data TimelineSync = TimelineSync {}
- data InvitedRoomSync = InvitedRoomSync
- data JoinedRoomSync = JoinedRoomSync {}
- data SyncResult = SyncResult {}
- data SyncResultRoom = SyncResultRoom {
- srrJoin :: Maybe (Map Text JoinedRoomSync)
- srrInvite :: Maybe (Map Text InvitedRoomSync)
Client
data ClientSession Source #
The session record, use createSession
to create it.
data LoginCredentials Source #
Constructors
LoginCredentials | |
Fields |
newtype MatrixToken Source #
Constructors
MatrixToken Text |
newtype InitialDeviceDisplayName Source #
Constructors
InitialDeviceDisplayName | |
Fields |
data LoginResponse Source #
Constructors
LoginResponse | |
Fields
|
Instances
FromJSON LoginResponse Source # | |
Defined in Network.Matrix.Internal Methods parseJSON :: Value -> Parser LoginResponse # parseJSONList :: Value -> Parser [LoginResponse] # |
Arguments
:: Text | The envirnoment variable name |
-> IO MatrixToken |
Arguments
:: Text | The matrix client-server base url, e.g. "https://matrix.org" |
-> MatrixToken | The user token |
-> IO ClientSession |
createSession
creates the session record.
login :: LoginCredentials -> IO ClientSession Source #
login
allows you to generate a session token.
loginToken :: LoginCredentials -> IO (ClientSession, MatrixToken) Source #
loginToken
allows you to generate a session token and recover the Matrix auth token.
API
type MatrixM m a = m (Either MatrixError a) Source #
data MatrixError Source #
Constructors
MatrixError | |
Instances
FromJSON MatrixError Source # | |
Defined in Network.Matrix.Internal | |
Show MatrixError Source # | |
Defined in Network.Matrix.Internal Methods showsPrec :: Int -> MatrixError -> ShowS # show :: MatrixError -> String # showList :: [MatrixError] -> ShowS # | |
Eq MatrixError Source # | |
Defined in Network.Matrix.Internal |
Arguments
:: (MonadMask m, MonadIO m) | |
=> Int | Maximum number of retry |
-> (Text -> m ()) | A log function, can be used to measure errors |
-> MatrixM m a | The action to retry |
-> MatrixM m a |
Retry a network action
User data
getTokenOwner :: ClientSession -> MatrixIO UserID Source #
getTokenOwner
gets information about the owner of a given access token.
Room Events
newtype MRCanonicalAlias Source #
Constructors
MRCanonicalAlias | |
Instances
FromJSON MRCanonicalAlias Source # | |
Defined in Network.Matrix.Client Methods parseJSON :: Value -> Parser MRCanonicalAlias # parseJSONList :: Value -> Parser [MRCanonicalAlias] # | |
Show MRCanonicalAlias Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> MRCanonicalAlias -> ShowS # show :: MRCanonicalAlias -> String # showList :: [MRCanonicalAlias] -> ShowS # |
newtype MRGuestAccess Source #
Constructors
MRGuestAccess | |
Fields |
Instances
FromJSON MRGuestAccess Source # | |
Defined in Network.Matrix.Client Methods parseJSON :: Value -> Parser MRGuestAccess # parseJSONList :: Value -> Parser [MRGuestAccess] # | |
Show MRGuestAccess Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> MRGuestAccess -> ShowS # show :: MRGuestAccess -> String # showList :: [MRGuestAccess] -> ShowS # |
newtype MRHistoryVisibility Source #
Constructors
MRHistoryVisibility | |
Fields |
Instances
FromJSON MRHistoryVisibility Source # | |
Defined in Network.Matrix.Client Methods parseJSON :: Value -> Parser MRHistoryVisibility # parseJSONList :: Value -> Parser [MRHistoryVisibility] # | |
Show MRHistoryVisibility Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> MRHistoryVisibility -> ShowS # show :: MRHistoryVisibility -> String # showList :: [MRHistoryVisibility] -> ShowS # |
data PaginatedRoomMessages Source #
Constructors
PaginatedRoomMessages | |
Instances
FromJSON PaginatedRoomMessages Source # | |
Defined in Network.Matrix.Client Methods parseJSON :: Value -> Parser PaginatedRoomMessages # parseJSONList :: Value -> Parser [PaginatedRoomMessages] # | |
Show PaginatedRoomMessages Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> PaginatedRoomMessages -> ShowS # show :: PaginatedRoomMessages -> String # showList :: [PaginatedRoomMessages] -> ShowS # |
data StateEvent Source #
Constructors
StateEvent | |
Fields
|
Instances
FromJSON StateEvent Source # | |
Defined in Network.Matrix.Client | |
Show StateEvent Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> StateEvent -> ShowS # show :: StateEvent -> String # showList :: [StateEvent] -> ShowS # |
data StateContent Source #
Constructors
StRoomCreate MRCreate | |
StRoomCanonicalAlias MRCanonicalAlias | StRoomMember MRMember | StRoomPowerLevels MRPowerLevels | StRoomJoinRules MRJoinRules |
StRoomGuestAccess MRGuestAccess | |
StRoomHistoryVisibility MRHistoryVisibility | |
StRoomName MRName | |
StRoomTopic MRTopic | |
StOther Value |
Instances
FromJSON StateContent Source # | |
Defined in Network.Matrix.Client | |
Show StateContent Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> StateContent -> ShowS # show :: StateContent -> String # showList :: [StateContent] -> ShowS # |
getRoomEvent :: ClientSession -> RoomID -> EventID -> MatrixIO RoomEvent Source #
getRoomMembers :: ClientSession -> RoomID -> MatrixIO (Map UserID User) Source #
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
getRoomState :: ClientSession -> RoomID -> MatrixIO [StateEvent] Source #
Get the state events for the current state of a room. https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3roomsroomidstate
getRoomStateEvent :: ClientSession -> RoomID -> EventType -> StateKey -> MatrixIO StateEvent Source #
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
Arguments
:: ClientSession | |
-> RoomID | The room to get events from. |
-> Dir | The direction to return events from. |
-> Maybe RoomEventFilter | A |
-> Text | The Since value to start returning events from. |
-> Maybe Int | The maximum number of events to return. Default: 10. |
-> Maybe Int | The token to stop returning events at. |
-> MatrixIO PaginatedRoomMessages |
sendRoomStateEvent :: ClientSession -> RoomID -> EventType -> StateKey -> Value -> MatrixIO EventID Source #
Send arbitrary state events to a room. These events will be overwritten if id, type and key all match. https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3roomsroomidstateeventtypestatekey
Room management
data RoomCreatePreset Source #
Constructors
PrivateChat | |
TrustedPrivateChat | |
PublicChat |
Instances
ToJSON RoomCreatePreset Source # | |
Defined in Network.Matrix.Room Methods toJSON :: RoomCreatePreset -> Value # toEncoding :: RoomCreatePreset -> Encoding # toJSONList :: [RoomCreatePreset] -> Value # toEncodingList :: [RoomCreatePreset] -> Encoding # | |
Show RoomCreatePreset Source # | |
Defined in Network.Matrix.Room Methods showsPrec :: Int -> RoomCreatePreset -> ShowS # show :: RoomCreatePreset -> String # showList :: [RoomCreatePreset] -> ShowS # | |
Eq RoomCreatePreset Source # | |
Defined in Network.Matrix.Room Methods (==) :: RoomCreatePreset -> RoomCreatePreset -> Bool # (/=) :: RoomCreatePreset -> RoomCreatePreset -> Bool # |
data RoomCreateRequest Source #
Constructors
RoomCreateRequest | |
Fields
|
Instances
createRoom :: ClientSession -> RoomCreateRequest -> MatrixIO RoomID Source #
Create a new room with various configuration options. https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3createroom
Room participation
data ResolvedRoomAlias Source #
Constructors
ResolvedRoomAlias | |
Instances
Show ResolvedRoomAlias Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> ResolvedRoomAlias -> ShowS # show :: ResolvedRoomAlias -> String # showList :: [ResolvedRoomAlias] -> ShowS # |
sendMessage :: ClientSession -> RoomID -> Event -> TxnID -> MatrixIO EventID Source #
This endpoint is used to send a message event to a room. https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3roomsroomidsendeventtypetxnid
Arguments
:: RoomID | The destination room, must match the original event |
-> RoomEvent | The original event |
-> MessageText | The reply message |
-> Event | The event to send |
Prepare a reply event
data MessageTextType Source #
Constructors
TextType | |
EmoteType | |
NoticeType |
Instances
FromJSON MessageTextType Source # | |
Defined in Network.Matrix.Events Methods parseJSON :: Value -> Parser MessageTextType # parseJSONList :: Value -> Parser [MessageTextType] # | |
ToJSON MessageTextType Source # | |
Defined in Network.Matrix.Events Methods toJSON :: MessageTextType -> Value # toEncoding :: MessageTextType -> Encoding # toJSONList :: [MessageTextType] -> Value # toEncodingList :: [MessageTextType] -> Encoding # | |
Show MessageTextType Source # | |
Defined in Network.Matrix.Events Methods showsPrec :: Int -> MessageTextType -> ShowS # show :: MessageTextType -> String # showList :: [MessageTextType] -> ShowS # | |
Eq MessageTextType Source # | |
Defined in Network.Matrix.Events Methods (==) :: MessageTextType -> MessageTextType -> Bool # (/=) :: MessageTextType -> MessageTextType -> Bool # |
data MessageText Source #
Constructors
MessageText | |
Fields
|
Instances
FromJSON MessageText Source # | |
Defined in Network.Matrix.Events | |
ToJSON MessageText Source # | |
Defined in Network.Matrix.Events Methods toJSON :: MessageText -> Value # toEncoding :: MessageText -> Encoding # toJSONList :: [MessageText] -> Value # toEncodingList :: [MessageText] -> Encoding # | |
Show MessageText Source # | |
Defined in Network.Matrix.Events Methods showsPrec :: Int -> MessageText -> ShowS # show :: MessageText -> String # showList :: [MessageText] -> ShowS # | |
Eq MessageText Source # | |
Defined in Network.Matrix.Events |
newtype RoomMessage Source #
Constructors
RoomMessageText MessageText |
Instances
FromJSON RoomMessage Source # | |
Defined in Network.Matrix.Events | |
ToJSON RoomMessage Source # | |
Defined in Network.Matrix.Events Methods toJSON :: RoomMessage -> Value # toEncoding :: RoomMessage -> Encoding # toJSONList :: [RoomMessage] -> Value # toEncodingList :: [RoomMessage] -> Encoding # | |
Show RoomMessage Source # | |
Defined in Network.Matrix.Events Methods showsPrec :: Int -> RoomMessage -> ShowS # show :: RoomMessage -> String # showList :: [RoomMessage] -> ShowS # | |
Eq RoomMessage Source # | |
Defined in Network.Matrix.Events |
Constructors
EventRoomMessage RoomMessage | |
EventRoomReply EventID RoomMessage | A reply defined by the parent event id and the reply message |
EventRoomEdit (EventID, RoomMessage) RoomMessage | An edit defined by the original message and the new message |
EventUnknown Object |
setRoomAlias :: ClientSession -> RoomAlias -> RoomID -> MatrixIO () Source #
Create a mapping of room alias to room ID. https://spec.matrix.org/v1.1/client-server-api/#put_matrixclientv3directoryroomroomalias
setRoomVisibility :: ClientSession -> RoomID -> Visibility -> MatrixIO () Source #
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
resolveRoomAlias :: ClientSession -> RoomAlias -> MatrixIO ResolvedRoomAlias Source #
Requests that the server resolve a room alias to a room ID. https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3directoryroomroomalias
deleteRoomAlias :: ClientSession -> RoomAlias -> MatrixIO () Source #
Delete a mapping of room alias to room ID. https://spec.matrix.org/v1.1/client-server-api/#delete_matrixclientv3directoryroomroomalias
getRoomAliases :: ClientSession -> RoomID -> MatrixIO [RoomAlias] Source #
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
Room membership
Instances
Show RoomAlias Source # | |
Eq RoomAlias Source # | |
Ord RoomAlias Source # | |
Hashable RoomAlias Source # | |
Defined in Network.Matrix.Client |
banUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO () Source #
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
checkRoomVisibility :: ClientSession -> RoomID -> MatrixIO Visibility Source #
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
forgetRoom :: ClientSession -> RoomID -> MatrixIO () Source #
Stops remembering a particular room. https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidforget
getJoinedRooms :: ClientSession -> MatrixIO [RoomID] Source #
Returns a list of the user’s current rooms. https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3joined_rooms
getPublicRooms :: ClientSession -> Maybe Int -> Maybe PaginationChunk -> MatrixIO PublicRooms Source #
Lists the public rooms on the server. https://spec.matrix.org/v1.1/client-server-api/#get_matrixclientv3publicrooms
getPublicRooms' :: ClientSession -> Maybe Int -> Maybe PaginationChunk -> Maybe Text -> Maybe Bool -> Maybe ThirdPartyInstanceId -> MatrixIO PublicRooms Source #
Lists the public rooms on the server, with optional filter. https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3publicrooms
inviteToRoom :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO () Source #
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
joinRoom :: ClientSession -> Text -> MatrixIO RoomID Source #
Note that this API takes either a room ID or alias, unlike joinRoomById
https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3joinroomidoralias
joinRoomById :: ClientSession -> RoomID -> MatrixIO RoomID Source #
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
leaveRoomById :: ClientSession -> RoomID -> MatrixIO () Source #
Stop participating in a particular room. https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidleave
kickUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO () Source #
Kick a user from the room. https://spec.matrix.org/v1.1/client-server-api/#post_matrixclientv3roomsroomidkick
knockOnRoom :: ClientSession -> Either RoomID RoomAlias -> [Text] -> Maybe Text -> MatrixIO RoomID Source #
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
unbanUser :: ClientSession -> RoomID -> UserID -> Maybe Text -> MatrixIO () Source #
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
Filter
data EventFormat Source #
Constructors
Client | |
Federation |
Instances
FromJSON EventFormat Source # | |
Defined in Network.Matrix.Client | |
ToJSON EventFormat Source # | |
Defined in Network.Matrix.Client Methods toJSON :: EventFormat -> Value # toEncoding :: EventFormat -> Encoding # toJSONList :: [EventFormat] -> Value # toEncodingList :: [EventFormat] -> Encoding # | |
Show EventFormat Source # | |
Defined in Network.Matrix.Client Methods showsPrec :: Int -> EventFormat -> ShowS # show :: EventFormat -> String # showList :: [EventFormat] -> ShowS # | |
Eq EventFormat Source # | |
Defined in Network.Matrix.Client |
data EventFilter Source #
Constructors
EventFilter | |
Instances
eventFilterAll :: EventFilter Source #
A filter that should match nothing
data RoomEventFilter Source #
Constructors
RoomEventFilter | |
Fields
|
Instances
roomEventFilterAll :: RoomEventFilter Source #
A filter that should match nothing
data StateFilter Source #
Constructors
StateFilter | |
Fields
|
Instances
data RoomFilter Source #
Constructors
RoomFilter | |
Fields
|
Instances
Constructors
Filter | |
Fields |
Instances
FromJSON Filter Source # | |
ToJSON Filter Source # | |
Defined in Network.Matrix.Client | |
Generic Filter Source # | |
Show Filter Source # | |
Eq Filter Source # | |
type Rep Filter Source # | |
Defined in Network.Matrix.Client type Rep Filter = D1 ('MetaData "Filter" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "Filter" 'PrefixI 'True) ((S1 ('MetaSel ('Just "filterEventFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "filterEventFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EventFormat))) :*: (S1 ('MetaSel ('Just "filterPresence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EventFilter)) :*: (S1 ('MetaSel ('Just "filterAccountData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EventFilter)) :*: S1 ('MetaSel ('Just "filterRoom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RoomFilter)))))) |
messageFilter :: Filter Source #
A filter to keep all the messages
Arguments
:: ClientSession | The client session, use |
-> UserID | The userID, use |
-> Filter | The filter definition, use |
-> MatrixIO FilterID | The function returns a |
Upload a new filter definition to the homeserver https://matrix.org/docs/spec/client_server/latest#post-matrix-client-r0-user-userid-filter
Account data
class (FromJSON a, ToJSON a) => AccountData a where Source #
Methods
accountDataType :: proxy a -> Text Source #
getAccountData :: forall a. AccountData a => ClientSession -> UserID -> MatrixIO a Source #
getAccountData' :: FromJSON a => ClientSession -> UserID -> Text -> MatrixIO a Source #
setAccountData :: forall a. AccountData a => ClientSession -> UserID -> a -> MatrixIO () Source #
setAccountData' :: ToJSON a => ClientSession -> UserID -> Text -> a -> MatrixIO () Source #
Events
sync :: ClientSession -> Maybe FilterID -> Maybe Text -> Maybe Presence -> Maybe Int -> MatrixIO SyncResult Source #
getTimelines :: SyncResult -> [(RoomID, NonEmpty RoomEvent)] Source #
Extract room events from a sync result
Arguments
:: MonadIO m | |
=> ClientSession | The client session, use |
-> Maybe FilterID | A sync filter, use |
-> Maybe Text | A since value, get it from a previous sync result using the |
-> Maybe Presence | Set the session presence. |
-> (SyncResult -> m ()) | Your callback to handle sync result. |
-> MatrixM m () | This function does not return unless there is an error. |
Constructors
Offline | |
Online | |
Unavailable |
Constructors
RoomEvent | |
Instances
FromJSON RoomEvent Source # | |
ToJSON RoomEvent Source # | |
Defined in Network.Matrix.Client | |
Generic RoomEvent Source # | |
Show RoomEvent Source # | |
Eq RoomEvent Source # | |
type Rep RoomEvent Source # | |
Defined in Network.Matrix.Client type Rep RoomEvent = D1 ('MetaData "RoomEvent" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "RoomEvent" 'PrefixI 'True) ((S1 ('MetaSel ('Just "reContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Event) :*: S1 ('MetaSel ('Just "reType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "reEventId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EventID) :*: S1 ('MetaSel ('Just "reSender") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Author)))) |
data RoomSummary Source #
Constructors
RoomSummary | |
Fields |
Instances
data TimelineSync Source #
Constructors
TimelineSync | |
Instances
data InvitedRoomSync Source #
Constructors
InvitedRoomSync |
Instances
data JoinedRoomSync Source #
Constructors
JoinedRoomSync | |
Fields |
Instances
data SyncResult Source #
Constructors
SyncResult | |
Fields |
Instances
data SyncResultRoom Source #
Constructors
SyncResultRoom | |
Fields
|