matrix-client-0.1.5.0: A matrix client library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.Matrix.Client

Description

This module contains the client-server API https://matrix.org/docs/spec/client_server/r0.6.1

Synopsis

Client

data ClientSession Source #

The session record, use createSession to create it.

newtype MatrixToken Source #

Constructors

MatrixToken Text 

newtype Username Source #

Constructors

Username 

Fields

newtype DeviceId Source #

Constructors

DeviceId 

Fields

getTokenFromEnv Source #

Arguments

:: Text

The envirnoment variable name

-> IO MatrixToken 

createSession Source #

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.

logout :: ClientSession -> MatrixIO () Source #

logout allows you to destroy a session token.

API

type MatrixM m a = m (Either MatrixError a) Source #

type MatrixIO a = MatrixM IO a Source #

MatrixIO is a convenient type alias for server response

retry :: (MonadIO m, MonadMask m) => MatrixM m a -> MatrixM m a Source #

retryWithLog Source #

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

newtype UserID Source #

Constructors

UserID Text 

Instances

Instances details
FromJSON UserID Source # 
Instance details

Defined in Network.Matrix.Internal

FromJSONKey UserID Source # 
Instance details

Defined in Network.Matrix.Internal

Show UserID Source # 
Instance details

Defined in Network.Matrix.Internal

Eq UserID Source # 
Instance details

Defined in Network.Matrix.Internal

Methods

(==) :: UserID -> UserID -> Bool #

(/=) :: UserID -> UserID -> Bool #

Ord UserID Source # 
Instance details

Defined in Network.Matrix.Internal

Hashable UserID Source # 
Instance details

Defined in Network.Matrix.Internal

Methods

hashWithSalt :: Int -> UserID -> Int #

hash :: UserID -> Int #

getTokenOwner :: ClientSession -> MatrixIO UserID Source #

getTokenOwner gets information about the owner of a given access token.

Room Events

data Dir Source #

Constructors

F

Forward

B

Backward

newtype EventType Source #

Constructors

EventType Text 

Instances

Instances details
FromJSON EventType Source # 
Instance details

Defined in Network.Matrix.Client

Show EventType Source # 
Instance details

Defined in Network.Matrix.Client

data MRCreate Source #

Constructors

MRCreate 

Instances

Instances details
FromJSON MRCreate Source # 
Instance details

Defined in Network.Matrix.Client

Show MRCreate Source # 
Instance details

Defined in Network.Matrix.Client

newtype MRGuestAccess Source #

Constructors

MRGuestAccess 

Fields

newtype MRName Source #

Constructors

MRName 

Fields

Instances

Instances details
FromJSON MRName Source # 
Instance details

Defined in Network.Matrix.Client

Show MRName Source # 
Instance details

Defined in Network.Matrix.Client

newtype MRTopic Source #

Constructors

MRTopic 

Fields

Instances

Instances details
FromJSON MRTopic Source # 
Instance details

Defined in Network.Matrix.Client

Show MRTopic Source # 
Instance details

Defined in Network.Matrix.Client

data PaginatedRoomMessages Source #

Constructors

PaginatedRoomMessages 

Fields

newtype StateKey Source #

Constructors

StateKey Text 

Instances

Instances details
FromJSON StateKey Source # 
Instance details

Defined in Network.Matrix.Client

Show StateKey Source # 
Instance details

Defined in Network.Matrix.Client

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

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

getRoomMessages Source #

Arguments

:: ClientSession 
-> RoomID

The room to get events from.

-> Dir

The direction to return events from.

-> Maybe RoomEventFilter

A RoomEventFilter to filter returned events with.

-> 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 

Room management

data RoomCreateRequest Source #

Instances

Instances details
ToJSON RoomCreateRequest Source # 
Instance details

Defined in Network.Matrix.Room

Generic RoomCreateRequest Source # 
Instance details

Defined in Network.Matrix.Room

Associated Types

type Rep RoomCreateRequest :: Type -> Type #

Show RoomCreateRequest Source # 
Instance details

Defined in Network.Matrix.Room

Eq RoomCreateRequest Source # 
Instance details

Defined in Network.Matrix.Room

type Rep RoomCreateRequest Source # 
Instance details

Defined in Network.Matrix.Room

type Rep RoomCreateRequest = D1 ('MetaData "RoomCreateRequest" "Network.Matrix.Room" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "RoomCreateRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rcrPreset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RoomCreatePreset) :*: S1 ('MetaSel ('Just "rcrRoomAliasName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "rcrName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "rcrTopic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

Room participation

data ResolvedRoomAlias Source #

Constructors

ResolvedRoomAlias 

Fields

Instances

Instances details
Show ResolvedRoomAlias Source # 
Instance details

Defined in Network.Matrix.Client

newtype TxnID Source #

Constructors

TxnID Text 

Instances

Instances details
Show TxnID Source # 
Instance details

Defined in Network.Matrix.Client

Methods

showsPrec :: Int -> TxnID -> ShowS #

show :: TxnID -> String #

showList :: [TxnID] -> ShowS #

Eq TxnID Source # 
Instance details

Defined in Network.Matrix.Client

Methods

(==) :: TxnID -> TxnID -> Bool #

(/=) :: TxnID -> TxnID -> Bool #

mkReply Source #

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 Event Source #

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 

Instances

Instances details
FromJSON Event Source # 
Instance details

Defined in Network.Matrix.Events

ToJSON Event Source # 
Instance details

Defined in Network.Matrix.Events

Show Event Source # 
Instance details

Defined in Network.Matrix.Events

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event Source # 
Instance details

Defined in Network.Matrix.Events

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

newtype EventID Source #

Constructors

EventID 

Fields

Instances

Instances details
FromJSON EventID Source # 
Instance details

Defined in Network.Matrix.Events

ToJSON EventID Source # 
Instance details

Defined in Network.Matrix.Events

Show EventID Source # 
Instance details

Defined in Network.Matrix.Events

Eq EventID Source # 
Instance details

Defined in Network.Matrix.Events

Methods

(==) :: EventID -> EventID -> Bool #

(/=) :: EventID -> EventID -> Bool #

Ord EventID Source # 
Instance details

Defined in Network.Matrix.Events

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

Room membership

newtype RoomID Source #

Constructors

RoomID Text 

Instances

Instances details
FromJSON RoomID Source # 
Instance details

Defined in Network.Matrix.Client

Show RoomID Source # 
Instance details

Defined in Network.Matrix.Client

Eq RoomID Source # 
Instance details

Defined in Network.Matrix.Client

Methods

(==) :: RoomID -> RoomID -> Bool #

(/=) :: RoomID -> RoomID -> Bool #

Ord RoomID Source # 
Instance details

Defined in Network.Matrix.Client

Hashable RoomID Source # 
Instance details

Defined in Network.Matrix.Client

Methods

hashWithSalt :: Int -> RoomID -> Int #

hash :: RoomID -> Int #

newtype RoomAlias Source #

Constructors

RoomAlias Text 

Instances

Instances details
Show RoomAlias Source # 
Instance details

Defined in Network.Matrix.Client

Eq RoomAlias Source # 
Instance details

Defined in Network.Matrix.Client

Ord RoomAlias Source # 
Instance details

Defined in Network.Matrix.Client

Hashable RoomAlias Source # 
Instance details

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

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

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

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 EventFilter Source #

Instances

Instances details
FromJSON EventFilter Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON EventFilter Source # 
Instance details

Defined in Network.Matrix.Client

Generic EventFilter Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep EventFilter :: Type -> Type #

Show EventFilter Source # 
Instance details

Defined in Network.Matrix.Client

Eq EventFilter Source # 
Instance details

Defined in Network.Matrix.Client

type Rep EventFilter Source # 
Instance details

Defined in Network.Matrix.Client

type Rep EventFilter = D1 ('MetaData "EventFilter" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "EventFilter" 'PrefixI 'True) ((S1 ('MetaSel ('Just "efLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "efNotSenders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text]))) :*: (S1 ('MetaSel ('Just "efNotTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: (S1 ('MetaSel ('Just "efSenders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text])) :*: S1 ('MetaSel ('Just "efTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Text]))))))

eventFilterAll :: EventFilter Source #

A filter that should match nothing

data RoomEventFilter Source #

Instances

Instances details
FromJSON RoomEventFilter Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON RoomEventFilter Source # 
Instance details

Defined in Network.Matrix.Client

Generic RoomEventFilter Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep RoomEventFilter :: Type -> Type #

Show RoomEventFilter Source # 
Instance details

Defined in Network.Matrix.Client

Eq RoomEventFilter Source # 
Instance details

Defined in Network.Matrix.Client

type Rep RoomEventFilter Source # 
Instance details

Defined in Network.Matrix.Client

roomEventFilterAll :: RoomEventFilter Source #

A filter that should match nothing

data StateFilter Source #

Instances

Instances details
FromJSON StateFilter Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON StateFilter Source # 
Instance details

Defined in Network.Matrix.Client

Generic StateFilter Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep StateFilter :: Type -> Type #

Show StateFilter Source # 
Instance details

Defined in Network.Matrix.Client

Eq StateFilter Source # 
Instance details

Defined in Network.Matrix.Client

type Rep StateFilter Source # 
Instance details

Defined in Network.Matrix.Client

data RoomFilter Source #

Instances

Instances details
FromJSON RoomFilter Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON RoomFilter Source # 
Instance details

Defined in Network.Matrix.Client

Generic RoomFilter Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep RoomFilter :: Type -> Type #

Show RoomFilter Source # 
Instance details

Defined in Network.Matrix.Client

Eq RoomFilter Source # 
Instance details

Defined in Network.Matrix.Client

type Rep RoomFilter Source # 
Instance details

Defined in Network.Matrix.Client

data Filter Source #

Instances

Instances details
FromJSON Filter Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON Filter Source # 
Instance details

Defined in Network.Matrix.Client

Generic Filter Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep Filter :: Type -> Type #

Methods

from :: Filter -> Rep Filter x #

to :: Rep Filter x -> Filter #

Show Filter Source # 
Instance details

Defined in Network.Matrix.Client

Eq Filter Source # 
Instance details

Defined in Network.Matrix.Client

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

type Rep Filter Source # 
Instance details

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))))))

newtype FilterID Source #

Constructors

FilterID Text 

Instances

Instances details
FromJSON FilterID Source # 
Instance details

Defined in Network.Matrix.Client

Show FilterID Source # 
Instance details

Defined in Network.Matrix.Client

Eq FilterID Source # 
Instance details

Defined in Network.Matrix.Client

Hashable FilterID Source # 
Instance details

Defined in Network.Matrix.Client

Methods

hashWithSalt :: Int -> FilterID -> Int #

hash :: FilterID -> Int #

messageFilter :: Filter Source #

A filter to keep all the messages

createFilter Source #

Arguments

:: ClientSession

The client session, use createSession to get one.

-> UserID

The userID, use getTokenOwner to get it.

-> Filter

The filter definition, use defaultFilter to create one or use the messageFilter example.

-> MatrixIO FilterID

The function returns a FilterID suitable for the sync function.

Account data

class (FromJSON a, ToJSON a) => AccountData a where Source #

Methods

accountDataType :: proxy a -> Text Source #

Events

getTimelines :: SyncResult -> [(RoomID, NonEmpty RoomEvent)] Source #

Extract room events from a sync result

syncPoll Source #

Arguments

:: MonadIO m 
=> ClientSession

The client session, use createSession to get one.

-> Maybe FilterID

A sync filter, use createFilter to get one.

-> Maybe Text

A since value, get it from a previous sync result using the srNextBatch field.

-> 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.

newtype Author Source #

Constructors

Author 

Fields

Instances

Instances details
FromJSON Author Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON Author Source # 
Instance details

Defined in Network.Matrix.Client

Show Author Source # 
Instance details

Defined in Network.Matrix.Client

Eq Author Source # 
Instance details

Defined in Network.Matrix.Client

Methods

(==) :: Author -> Author -> Bool #

(/=) :: Author -> Author -> Bool #

data Presence Source #

Constructors

Offline 
Online 
Unavailable 

Instances

Instances details
FromJSON Presence Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON Presence Source # 
Instance details

Defined in Network.Matrix.Client

Show Presence Source # 
Instance details

Defined in Network.Matrix.Client

Eq Presence Source # 
Instance details

Defined in Network.Matrix.Client

data RoomEvent Source #

Constructors

RoomEvent 

Instances

Instances details
FromJSON RoomEvent Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON RoomEvent Source # 
Instance details

Defined in Network.Matrix.Client

Generic RoomEvent Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep RoomEvent :: Type -> Type #

Show RoomEvent Source # 
Instance details

Defined in Network.Matrix.Client

Eq RoomEvent Source # 
Instance details

Defined in Network.Matrix.Client

type Rep RoomEvent Source # 
Instance details

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 #

Instances

Instances details
FromJSON RoomSummary Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON RoomSummary Source # 
Instance details

Defined in Network.Matrix.Client

Generic RoomSummary Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep RoomSummary :: Type -> Type #

Show RoomSummary Source # 
Instance details

Defined in Network.Matrix.Client

Eq RoomSummary Source # 
Instance details

Defined in Network.Matrix.Client

type Rep RoomSummary Source # 
Instance details

Defined in Network.Matrix.Client

type Rep RoomSummary = D1 ('MetaData "RoomSummary" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "RoomSummary" 'PrefixI 'True) (S1 ('MetaSel ('Just "rsJoinedMemberCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "rsInvitedMemberCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))

data TimelineSync Source #

Instances

Instances details
FromJSON TimelineSync Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON TimelineSync Source # 
Instance details

Defined in Network.Matrix.Client

Generic TimelineSync Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep TimelineSync :: Type -> Type #

Show TimelineSync Source # 
Instance details

Defined in Network.Matrix.Client

Eq TimelineSync Source # 
Instance details

Defined in Network.Matrix.Client

type Rep TimelineSync Source # 
Instance details

Defined in Network.Matrix.Client

type Rep TimelineSync = D1 ('MetaData "TimelineSync" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "TimelineSync" 'PrefixI 'True) (S1 ('MetaSel ('Just "tsEvents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [RoomEvent])) :*: (S1 ('MetaSel ('Just "tsLimited") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "tsPrevBatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data InvitedRoomSync Source #

Constructors

InvitedRoomSync 

Instances

Instances details
FromJSON InvitedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON InvitedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

Generic InvitedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep InvitedRoomSync :: Type -> Type #

Show InvitedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

Eq InvitedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

type Rep InvitedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

type Rep InvitedRoomSync = D1 ('MetaData "InvitedRoomSync" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "InvitedRoomSync" 'PrefixI 'False) (U1 :: Type -> Type))

data JoinedRoomSync Source #

Instances

Instances details
FromJSON JoinedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON JoinedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

Generic JoinedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep JoinedRoomSync :: Type -> Type #

Show JoinedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

Eq JoinedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

type Rep JoinedRoomSync Source # 
Instance details

Defined in Network.Matrix.Client

type Rep JoinedRoomSync = D1 ('MetaData "JoinedRoomSync" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "JoinedRoomSync" 'PrefixI 'True) (S1 ('MetaSel ('Just "jrsSummary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe RoomSummary)) :*: S1 ('MetaSel ('Just "jrsTimeline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimelineSync)))

data SyncResult Source #

Instances

Instances details
FromJSON SyncResult Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON SyncResult Source # 
Instance details

Defined in Network.Matrix.Client

Generic SyncResult Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep SyncResult :: Type -> Type #

Show SyncResult Source # 
Instance details

Defined in Network.Matrix.Client

Eq SyncResult Source # 
Instance details

Defined in Network.Matrix.Client

type Rep SyncResult Source # 
Instance details

Defined in Network.Matrix.Client

type Rep SyncResult = D1 ('MetaData "SyncResult" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "SyncResult" 'PrefixI 'True) (S1 ('MetaSel ('Just "srNextBatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "srRooms") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SyncResultRoom))))

data SyncResultRoom Source #

Instances

Instances details
FromJSON SyncResultRoom Source # 
Instance details

Defined in Network.Matrix.Client

ToJSON SyncResultRoom Source # 
Instance details

Defined in Network.Matrix.Client

Generic SyncResultRoom Source # 
Instance details

Defined in Network.Matrix.Client

Associated Types

type Rep SyncResultRoom :: Type -> Type #

Show SyncResultRoom Source # 
Instance details

Defined in Network.Matrix.Client

Eq SyncResultRoom Source # 
Instance details

Defined in Network.Matrix.Client

type Rep SyncResultRoom Source # 
Instance details

Defined in Network.Matrix.Client

type Rep SyncResultRoom = D1 ('MetaData "SyncResultRoom" "Network.Matrix.Client" "matrix-client-0.1.5.0-8hA0zxvoqujEIAR2je6bZW" 'False) (C1 ('MetaCons "SyncResultRoom" 'PrefixI 'True) (S1 ('MetaSel ('Just "srrJoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text JoinedRoomSync))) :*: S1 ('MetaSel ('Just "srrInvite") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text InvitedRoomSync)))))