Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ConnectionPoolConfig = ConnectionPoolConfig {}
- data Login = Login {}
- type Hostname = Text
- type Port = Int
- data ConnectionData
- data Session
- newtype Id = Id {}
- data User = User {
- userId :: UserId
- userCreateAt :: Maybe ServerTime
- userUpdateAt :: Maybe ServerTime
- userDeleteAt :: ServerTime
- userUsername :: Text
- userAuthData :: Maybe Text
- userAuthService :: Text
- userEmail :: UserText
- userEmailVerified :: Bool
- userNickname :: UserText
- userFirstName :: UserText
- userLastName :: UserText
- userRoles :: Text
- userNotifyProps :: UserNotifyProps
- userLastPasswordUpdate :: Maybe ServerTime
- userLastPictureUpdate :: Maybe ServerTime
- userLocale :: Text
- newtype UserId = UI {}
- data InitialLoad = InitialLoad {}
- data Team = Team {}
- data TeamMember = TeamMember {}
- data Type
- newtype TeamId = TI {}
- data TeamsCreate = TeamsCreate {}
- data Channel = Channel {
- channelId :: ChannelId
- channelCreateAt :: ServerTime
- channelUpdateAt :: ServerTime
- channelDeleteAt :: ServerTime
- channelTeamId :: Maybe TeamId
- channelType :: Type
- channelDisplayName :: UserText
- channelName :: UserText
- channelHeader :: UserText
- channelPurpose :: UserText
- channelLastPostAt :: ServerTime
- channelTotalMsgCount :: Int
- channelCreatorId :: Maybe UserId
- data ChannelWithData = ChannelWithData Channel ChannelData
- data ChannelData = ChannelData {}
- newtype ChannelId = CI {}
- type Channels = Seq Channel
- data ConnectionType
- data MinChannel = MinChannel {}
- data UsersCreate = UsersCreate {}
- data Post = Post {
- postPendingPostId :: Maybe PostId
- postOriginalId :: Maybe PostId
- postProps :: PostProps
- postRootId :: Maybe PostId
- postFileIds :: Seq FileId
- postId :: PostId
- postType :: PostType
- postMessage :: UserText
- postDeleteAt :: Maybe ServerTime
- postHashtags :: Text
- postUpdateAt :: ServerTime
- postEditAt :: ServerTime
- postUserId :: Maybe UserId
- postCreateAt :: ServerTime
- postChannelId :: ChannelId
- postHasReactions :: Bool
- postPinned :: Maybe Bool
- data PostType
- data PostProps = PostProps {}
- data PendingPost = PendingPost {}
- newtype PostId = PI {}
- newtype FileId = FI {}
- data FileInfo = FileInfo {
- fileInfoId :: FileId
- fileInfoUserId :: UserId
- fileInfoPostId :: Maybe PostId
- fileInfoCreateAt :: ServerTime
- fileInfoUpdateAt :: ServerTime
- fileInfoDeleteAt :: ServerTime
- fileInfoName :: Text
- fileInfoExtension :: Text
- fileInfoSize :: Int
- fileInfoMimeType :: Text
- fileInfoWidth :: Maybe Int
- fileInfoHeight :: Maybe Int
- fileInfoHasPreview :: Bool
- data Reaction = Reaction {}
- urlForFile :: FileId -> Text
- data Posts = Posts {}
- data MinCommand = MinCommand {}
- data CommandResponse = CommandResponse {}
- data CommandResponseType
- data Preference = Preference {}
- data PreferenceCategory
- = PreferenceCategoryDirectChannelShow
- | PreferenceCategoryGroupChannelShow
- | PreferenceCategoryTutorialStep
- | PreferenceCategoryAdvancedSettings
- | PreferenceCategoryFlaggedPost
- | PreferenceCategoryDisplaySettings
- | PreferenceCategoryTheme
- | PreferenceCategoryAuthorizedOAuthApp
- | PreferenceCategoryNotifications
- | PreferenceCategoryLast
- | PreferenceCategoryOther Text
- data PreferenceName = PreferenceName {}
- data PreferenceValue = PreferenceValue {}
- data FlaggedPost = FlaggedPost {}
- preferenceToFlaggedPost :: Preference -> Maybe FlaggedPost
- type Logger = LogEvent -> IO ()
- data LogEvent = LogEvent {}
- data LogEventType
- withLogger :: ConnectionData -> Logger -> ConnectionData
- noLogger :: ConnectionData -> ConnectionData
- class HasId x y | x -> y where
- getId :: x -> y
- defaultConnectionPoolConfig :: ConnectionPoolConfig
- mkConnectionData :: Hostname -> Port -> Text -> Pool MMConn -> ConnectionType -> ConnectionContext -> ConnectionData
- initConnectionData :: Hostname -> Port -> Text -> ConnectionType -> ConnectionPoolConfig -> IO ConnectionData
- mmCloseSession :: Session -> IO ()
- mmLogin :: ConnectionData -> Login -> IO (Either LoginFailureException (Session, User))
- mmCreateDirect :: Session -> TeamId -> UserId -> IO Channel
- mmCreateChannel :: Session -> TeamId -> MinChannel -> IO Channel
- mmCreateGroupChannel :: Session -> [UserId] -> IO Channel
- mmCreateTeam :: Session -> TeamsCreate -> IO Team
- mmDeleteChannel :: Session -> TeamId -> ChannelId -> IO ()
- mmLeaveChannel :: Session -> TeamId -> ChannelId -> IO ()
- mmJoinChannel :: Session -> TeamId -> ChannelId -> IO ()
- mmGetTeams :: Session -> IO (HashMap TeamId Team)
- mmGetChannels :: Session -> TeamId -> IO Channels
- mmGetAllChannelsForUser :: Session -> TeamId -> UserId -> IO (Seq Channel)
- mmGetAllChannelDataForUser :: Session -> TeamId -> UserId -> IO (Seq ChannelData)
- mmGetAllChannelsWithDataForUser :: Session -> TeamId -> UserId -> IO (HashMap ChannelId ChannelWithData)
- mmGetMoreChannels :: Session -> TeamId -> Int -> Int -> IO Channels
- mmGetChannel :: Session -> TeamId -> ChannelId -> IO ChannelWithData
- mmViewChannel :: Session -> TeamId -> ChannelId -> Maybe ChannelId -> IO ()
- mmDeletePost :: Session -> TeamId -> ChannelId -> PostId -> IO ()
- mmGetPost :: Session -> TeamId -> ChannelId -> PostId -> IO Posts
- mmGetPosts :: Session -> TeamId -> ChannelId -> Int -> Int -> IO Posts
- mmGetPostsSince :: Session -> TeamId -> ChannelId -> ServerTime -> IO Posts
- mmGetPostsBefore :: Session -> TeamId -> ChannelId -> PostId -> Int -> Int -> IO Posts
- mmGetPostsAfter :: Session -> TeamId -> ChannelId -> PostId -> Int -> Int -> IO Posts
- mmSearchPosts :: Session -> TeamId -> Text -> Bool -> IO Posts
- mmGetReactionsForPost :: Session -> TeamId -> ChannelId -> PostId -> IO [Reaction]
- mmGetFileInfo :: Session -> FileId -> IO FileInfo
- mmGetFile :: Session -> FileId -> IO ByteString
- mmGetUser :: Session -> UserId -> IO User
- mmGetUsers :: Session -> Int -> Int -> IO (HashMap UserId User)
- mmGetTeamMembers :: Session -> TeamId -> IO (Seq TeamMember)
- mmGetChannelMembers :: Session -> TeamId -> ChannelId -> Int -> Int -> IO (HashMap UserId User)
- mmGetProfilesForDMList :: Session -> TeamId -> IO (HashMap UserId User)
- mmGetMe :: Session -> IO User
- mmGetProfiles :: Session -> TeamId -> Int -> Int -> IO (HashMap UserId User)
- mmGetStatuses :: Session -> IO (HashMap UserId Text)
- mmGetInitialLoad :: Session -> IO InitialLoad
- mmSaveConfig :: Session -> Value -> IO ()
- mmSetChannelHeader :: Session -> TeamId -> ChannelId -> Text -> IO Channel
- mmChannelAddUser :: Session -> TeamId -> ChannelId -> UserId -> IO ChannelData
- mmChannelRemoveUser :: Session -> ChannelId -> UserId -> IO ()
- mmTeamAddUser :: Session -> TeamId -> UserId -> IO ()
- mmUsersCreate :: ConnectionData -> UsersCreate -> IO User
- mmUsersCreateWithSession :: Session -> UsersCreate -> IO User
- mmPost :: Session -> TeamId -> PendingPost -> IO Post
- mmUpdatePost :: Session -> TeamId -> Post -> IO Post
- mmExecute :: Session -> TeamId -> MinCommand -> IO CommandResponse
- mmGetConfig :: Session -> IO Value
- mmGetClientConfig :: Session -> IO Value
- mmSetPreferences :: Session -> UserId -> Seq Preference -> IO ()
- mmSavePreferences :: Session -> Seq Preference -> IO ()
- mmDeletePreferences :: Session -> Seq Preference -> IO ()
- mmFlagPost :: Session -> UserId -> PostId -> IO ()
- mmUnflagPost :: Session -> UserId -> PostId -> IO ()
- mmGetFlaggedPosts :: Session -> UserId -> IO Posts
- mmGetMyPreferences :: Session -> IO (Seq Preference)
- mkPendingPost :: Text -> UserId -> ChannelId -> IO PendingPost
- idString :: IsId x => x -> Text
- hoistE :: Exception e => Either e r -> IO r
- noteE :: Exception e => Maybe r -> e -> IO r
- assertE :: Exception e => Bool -> e -> IO ()
Types
Mattermost-Related Types (deprecated: use Network.Mattermost.Types instead)
data ConnectionPoolConfig Source #
data ConnectionData Source #
Instances
Eq Id Source # | |
Ord Id Source # | |
Read Id Source # | |
Show Id Source # | |
Hashable Id Source # | |
Defined in Network.Mattermost.Types | |
ToJSON Id Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey Id Source # | |
Defined in Network.Mattermost.Types | |
FromJSON Id Source # | |
FromJSONKey Id Source # | |
Defined in Network.Mattermost.Types | |
IsId Id Source # | |
HasId Id Id Source # | |
Instances
Eq UserId Source # | |
Ord UserId Source # | |
Read UserId Source # | |
Show UserId Source # | |
Hashable UserId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON UserId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey UserId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON UserId Source # | |
FromJSONKey UserId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg UserId Source # | |
Defined in Network.Mattermost.Types formatArg :: UserId -> FieldFormatter # parseFormat :: UserId -> ModifierParser # | |
IsId UserId Source # | |
HasId User UserId Source # | |
data InitialLoad Source #
Instances
Eq InitialLoad Source # | |
Defined in Network.Mattermost.Types (==) :: InitialLoad -> InitialLoad -> Bool # (/=) :: InitialLoad -> InitialLoad -> Bool # | |
Show InitialLoad Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> InitialLoad -> ShowS # show :: InitialLoad -> String # showList :: [InitialLoad] -> ShowS # | |
FromJSON InitialLoad Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser InitialLoad # parseJSONList :: Value -> Parser [InitialLoad] # |
Team | |
|
data TeamMember Source #
Instances
Instances
Eq TeamId Source # | |
Ord TeamId Source # | |
Read TeamId Source # | |
Show TeamId Source # | |
Hashable TeamId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON TeamId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey TeamId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON TeamId Source # | |
FromJSONKey TeamId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg TeamId Source # | |
Defined in Network.Mattermost.Types formatArg :: TeamId -> FieldFormatter # parseFormat :: TeamId -> ModifierParser # | |
IsId TeamId Source # | |
HasId Team TeamId Source # | |
data TeamsCreate Source #
Instances
Eq TeamsCreate Source # | |
Defined in Network.Mattermost.Types (==) :: TeamsCreate -> TeamsCreate -> Bool # (/=) :: TeamsCreate -> TeamsCreate -> Bool # | |
Read TeamsCreate Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS TeamsCreate # readList :: ReadS [TeamsCreate] # readPrec :: ReadPrec TeamsCreate # readListPrec :: ReadPrec [TeamsCreate] # | |
Show TeamsCreate Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> TeamsCreate -> ShowS # show :: TeamsCreate -> String # showList :: [TeamsCreate] -> ShowS # | |
ToJSON TeamsCreate Source # | |
Defined in Network.Mattermost.Types toJSON :: TeamsCreate -> Value # toEncoding :: TeamsCreate -> Encoding # toJSONList :: [TeamsCreate] -> Value # toEncodingList :: [TeamsCreate] -> Encoding # |
data ChannelWithData Source #
Instances
Eq ChannelWithData Source # | |
Defined in Network.Mattermost.Types (==) :: ChannelWithData -> ChannelWithData -> Bool # (/=) :: ChannelWithData -> ChannelWithData -> Bool # | |
Read ChannelWithData Source # | |
Defined in Network.Mattermost.Types | |
Show ChannelWithData Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> ChannelWithData -> ShowS # show :: ChannelWithData -> String # showList :: [ChannelWithData] -> ShowS # | |
FromJSON ChannelWithData Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser ChannelWithData # parseJSONList :: Value -> Parser [ChannelWithData] # |
data ChannelData Source #
Instances
Eq ChannelData Source # | |
Defined in Network.Mattermost.Types (==) :: ChannelData -> ChannelData -> Bool # (/=) :: ChannelData -> ChannelData -> Bool # | |
Read ChannelData Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS ChannelData # readList :: ReadS [ChannelData] # readPrec :: ReadPrec ChannelData # readListPrec :: ReadPrec [ChannelData] # | |
Show ChannelData Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> ChannelData -> ShowS # show :: ChannelData -> String # showList :: [ChannelData] -> ShowS # | |
FromJSON ChannelData Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser ChannelData # parseJSONList :: Value -> Parser [ChannelData] # | |
HasId ChannelData ChannelId Source # | |
Defined in Network.Mattermost.Types getId :: ChannelData -> ChannelId Source # |
Instances
Eq ChannelId Source # | |
Ord ChannelId Source # | |
Defined in Network.Mattermost.Types | |
Read ChannelId Source # | |
Show ChannelId Source # | |
Hashable ChannelId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON ChannelId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey ChannelId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON ChannelId Source # | |
FromJSONKey ChannelId Source # | |
PrintfArg ChannelId Source # | |
Defined in Network.Mattermost.Types formatArg :: ChannelId -> FieldFormatter # parseFormat :: ChannelId -> ModifierParser # | |
IsId ChannelId Source # | |
HasId ChannelData ChannelId Source # | |
Defined in Network.Mattermost.Types getId :: ChannelData -> ChannelId Source # | |
HasId Channel ChannelId Source # | |
data ConnectionType Source #
ConnectHTTPS Bool | Boolean is whether to require trusted certificate |
ConnectHTTP | Make an insecure connection over HTTP |
Instances
Eq ConnectionType Source # | |
Defined in Network.Mattermost.Types.Internal (==) :: ConnectionType -> ConnectionType -> Bool # (/=) :: ConnectionType -> ConnectionType -> Bool # | |
Read ConnectionType Source # | |
Defined in Network.Mattermost.Types.Internal readsPrec :: Int -> ReadS ConnectionType # readList :: ReadS [ConnectionType] # | |
Show ConnectionType Source # | |
Defined in Network.Mattermost.Types.Internal showsPrec :: Int -> ConnectionType -> ShowS # show :: ConnectionType -> String # showList :: [ConnectionType] -> ShowS # |
data MinChannel Source #
Instances
Eq MinChannel Source # | |
Defined in Network.Mattermost.Types (==) :: MinChannel -> MinChannel -> Bool # (/=) :: MinChannel -> MinChannel -> Bool # | |
Read MinChannel Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS MinChannel # readList :: ReadS [MinChannel] # readPrec :: ReadPrec MinChannel # readListPrec :: ReadPrec [MinChannel] # | |
Show MinChannel Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> MinChannel -> ShowS # show :: MinChannel -> String # showList :: [MinChannel] -> ShowS # | |
ToJSON MinChannel Source # | |
Defined in Network.Mattermost.Types toJSON :: MinChannel -> Value # toEncoding :: MinChannel -> Encoding # toJSONList :: [MinChannel] -> Value # toEncodingList :: [MinChannel] -> Encoding # |
data UsersCreate Source #
Instances
Eq UsersCreate Source # | |
Defined in Network.Mattermost.Types (==) :: UsersCreate -> UsersCreate -> Bool # (/=) :: UsersCreate -> UsersCreate -> Bool # | |
Read UsersCreate Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS UsersCreate # readList :: ReadS [UsersCreate] # readPrec :: ReadPrec UsersCreate # readListPrec :: ReadPrec [UsersCreate] # | |
Show UsersCreate Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> UsersCreate -> ShowS # show :: UsersCreate -> String # showList :: [UsersCreate] -> ShowS # | |
ToJSON UsersCreate Source # | |
Defined in Network.Mattermost.Types toJSON :: UsersCreate -> Value # toEncoding :: UsersCreate -> Encoding # toJSONList :: [UsersCreate] -> Value # toEncodingList :: [UsersCreate] -> Encoding # |
Post | |
|
data PendingPost Source #
Instances
Eq PendingPost Source # | |
Defined in Network.Mattermost.Types (==) :: PendingPost -> PendingPost -> Bool # (/=) :: PendingPost -> PendingPost -> Bool # | |
Read PendingPost Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS PendingPost # readList :: ReadS [PendingPost] # readPrec :: ReadPrec PendingPost # readListPrec :: ReadPrec [PendingPost] # | |
Show PendingPost Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PendingPost -> ShowS # show :: PendingPost -> String # showList :: [PendingPost] -> ShowS # | |
ToJSON PendingPost Source # | |
Defined in Network.Mattermost.Types toJSON :: PendingPost -> Value # toEncoding :: PendingPost -> Encoding # toJSONList :: [PendingPost] -> Value # toEncodingList :: [PendingPost] -> Encoding # | |
HasId PendingPost PendingPostId Source # | |
Defined in Network.Mattermost.Types getId :: PendingPost -> PendingPostId Source # |
Instances
Eq PostId Source # | |
Ord PostId Source # | |
Read PostId Source # | |
Show PostId Source # | |
Hashable PostId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON PostId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey PostId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON PostId Source # | |
FromJSONKey PostId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg PostId Source # | |
Defined in Network.Mattermost.Types formatArg :: PostId -> FieldFormatter # parseFormat :: PostId -> ModifierParser # | |
IsId PostId Source # | |
HasId Post PostId Source # | |
Instances
Eq FileId Source # | |
Ord FileId Source # | |
Read FileId Source # | |
Show FileId Source # | |
Hashable FileId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON FileId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey FileId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON FileId Source # | |
FromJSONKey FileId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg FileId Source # | |
Defined in Network.Mattermost.Types formatArg :: FileId -> FieldFormatter # parseFormat :: FileId -> ModifierParser # | |
IsId FileId Source # | |
urlForFile :: FileId -> Text Source #
Posts | |
|
data MinCommand Source #
Instances
Eq MinCommand Source # | |
Defined in Network.Mattermost.Types (==) :: MinCommand -> MinCommand -> Bool # (/=) :: MinCommand -> MinCommand -> Bool # | |
Read MinCommand Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS MinCommand # readList :: ReadS [MinCommand] # readPrec :: ReadPrec MinCommand # readListPrec :: ReadPrec [MinCommand] # | |
Show MinCommand Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> MinCommand -> ShowS # show :: MinCommand -> String # showList :: [MinCommand] -> ShowS # | |
ToJSON MinCommand Source # | |
Defined in Network.Mattermost.Types toJSON :: MinCommand -> Value # toEncoding :: MinCommand -> Encoding # toJSONList :: [MinCommand] -> Value # toEncodingList :: [MinCommand] -> Encoding # |
data CommandResponse Source #
Instances
Eq CommandResponse Source # | |
Defined in Network.Mattermost.Types (==) :: CommandResponse -> CommandResponse -> Bool # (/=) :: CommandResponse -> CommandResponse -> Bool # | |
Read CommandResponse Source # | |
Defined in Network.Mattermost.Types | |
Show CommandResponse Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> CommandResponse -> ShowS # show :: CommandResponse -> String # showList :: [CommandResponse] -> ShowS # | |
FromJSON CommandResponse Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser CommandResponse # parseJSONList :: Value -> Parser [CommandResponse] # |
data CommandResponseType Source #
Instances
Eq CommandResponseType Source # | |
Defined in Network.Mattermost.Types (==) :: CommandResponseType -> CommandResponseType -> Bool # (/=) :: CommandResponseType -> CommandResponseType -> Bool # | |
Read CommandResponseType Source # | |
Defined in Network.Mattermost.Types | |
Show CommandResponseType Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> CommandResponseType -> ShowS # show :: CommandResponseType -> String # showList :: [CommandResponseType] -> ShowS # | |
FromJSON CommandResponseType Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser CommandResponseType # parseJSONList :: Value -> Parser [CommandResponseType] # |
data Preference Source #
Instances
Eq Preference Source # | |
Defined in Network.Mattermost.Types (==) :: Preference -> Preference -> Bool # (/=) :: Preference -> Preference -> Bool # | |
Read Preference Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS Preference # readList :: ReadS [Preference] # readPrec :: ReadPrec Preference # readListPrec :: ReadPrec [Preference] # | |
Show Preference Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> Preference -> ShowS # show :: Preference -> String # showList :: [Preference] -> ShowS # | |
ToJSON Preference Source # | |
Defined in Network.Mattermost.Types toJSON :: Preference -> Value # toEncoding :: Preference -> Encoding # toJSONList :: [Preference] -> Value # toEncodingList :: [Preference] -> Encoding # | |
FromJSON Preference Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser Preference # parseJSONList :: Value -> Parser [Preference] # |
data PreferenceCategory Source #
Instances
Eq PreferenceCategory Source # | |
Defined in Network.Mattermost.Types (==) :: PreferenceCategory -> PreferenceCategory -> Bool # (/=) :: PreferenceCategory -> PreferenceCategory -> Bool # | |
Read PreferenceCategory Source # | |
Defined in Network.Mattermost.Types | |
Show PreferenceCategory Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PreferenceCategory -> ShowS # show :: PreferenceCategory -> String # showList :: [PreferenceCategory] -> ShowS # | |
ToJSON PreferenceCategory Source # | |
Defined in Network.Mattermost.Types toJSON :: PreferenceCategory -> Value # toEncoding :: PreferenceCategory -> Encoding # toJSONList :: [PreferenceCategory] -> Value # toEncodingList :: [PreferenceCategory] -> Encoding # | |
FromJSON PreferenceCategory Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser PreferenceCategory # parseJSONList :: Value -> Parser [PreferenceCategory] # |
data PreferenceName Source #
Instances
Eq PreferenceName Source # | |
Defined in Network.Mattermost.Types (==) :: PreferenceName -> PreferenceName -> Bool # (/=) :: PreferenceName -> PreferenceName -> Bool # | |
Read PreferenceName Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS PreferenceName # readList :: ReadS [PreferenceName] # | |
Show PreferenceName Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PreferenceName -> ShowS # show :: PreferenceName -> String # showList :: [PreferenceName] -> ShowS # | |
ToJSON PreferenceName Source # | |
Defined in Network.Mattermost.Types toJSON :: PreferenceName -> Value # toEncoding :: PreferenceName -> Encoding # toJSONList :: [PreferenceName] -> Value # toEncodingList :: [PreferenceName] -> Encoding # | |
FromJSON PreferenceName Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser PreferenceName # parseJSONList :: Value -> Parser [PreferenceName] # |
data PreferenceValue Source #
Instances
Eq PreferenceValue Source # | |
Defined in Network.Mattermost.Types (==) :: PreferenceValue -> PreferenceValue -> Bool # (/=) :: PreferenceValue -> PreferenceValue -> Bool # | |
Read PreferenceValue Source # | |
Defined in Network.Mattermost.Types | |
Show PreferenceValue Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PreferenceValue -> ShowS # show :: PreferenceValue -> String # showList :: [PreferenceValue] -> ShowS # | |
ToJSON PreferenceValue Source # | |
Defined in Network.Mattermost.Types toJSON :: PreferenceValue -> Value # toEncoding :: PreferenceValue -> Encoding # toJSONList :: [PreferenceValue] -> Value # toEncodingList :: [PreferenceValue] -> Encoding # | |
FromJSON PreferenceValue Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser PreferenceValue # parseJSONList :: Value -> Parser [PreferenceValue] # |
data FlaggedPost Source #
Instances
Eq FlaggedPost Source # | |
Defined in Network.Mattermost.Types (==) :: FlaggedPost -> FlaggedPost -> Bool # (/=) :: FlaggedPost -> FlaggedPost -> Bool # | |
Read FlaggedPost Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS FlaggedPost # readList :: ReadS [FlaggedPost] # readPrec :: ReadPrec FlaggedPost # readListPrec :: ReadPrec [FlaggedPost] # | |
Show FlaggedPost Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> FlaggedPost -> ShowS # show :: FlaggedPost -> String # showList :: [FlaggedPost] -> ShowS # | |
ToJSON FlaggedPost Source # | |
Defined in Network.Mattermost.Types toJSON :: FlaggedPost -> Value # toEncoding :: FlaggedPost -> Encoding # toJSONList :: [FlaggedPost] -> Value # toEncodingList :: [FlaggedPost] -> Encoding # |
preferenceToFlaggedPost :: Preference -> Maybe FlaggedPost Source #
Attempt to expose a Preference
as a FlaggedPost
Log-related types
If there is a Logger
in the ConnectionData
struct, it will
be sporadically called with values of type LogEvent
.
data LogEventType Source #
A LogEventType
describes the particular event that happened
HttpRequest RequestMethod String (Maybe Value) | |
HttpResponse Int String (Maybe Value) | |
WebSocketRequest Value | |
WebSocketResponse (Either String Value) | Left means we got an exception trying to parse the response; Right means we succeeded and here it is. |
WebSocketPing | |
WebSocketPong |
Instances
Eq LogEventType Source # | |
Defined in Network.Mattermost.Types.Base (==) :: LogEventType -> LogEventType -> Bool # (/=) :: LogEventType -> LogEventType -> Bool # | |
Show LogEventType Source # | |
Defined in Network.Mattermost.Types.Base showsPrec :: Int -> LogEventType -> ShowS # show :: LogEventType -> String # showList :: [LogEventType] -> ShowS # |
withLogger :: ConnectionData -> Logger -> ConnectionData Source #
Typeclasses
class HasId x y | x -> y where Source #
Instances
HasId Command CommandId Source # | |
HasId PendingPost PendingPostId Source # | |
Defined in Network.Mattermost.Types getId :: PendingPost -> PendingPostId Source # | |
HasId Post PostId Source # | |
HasId User UserId Source # | |
HasId ChannelData ChannelId Source # | |
Defined in Network.Mattermost.Types getId :: ChannelData -> ChannelId Source # | |
HasId Channel ChannelId Source # | |
HasId Team TeamId Source # | |
HasId Id Id Source # | |
HTTP API Functions
mkConnectionData :: Hostname -> Port -> Text -> Pool MMConn -> ConnectionType -> ConnectionContext -> ConnectionData Source #
Creates a structure representing a connection to the server.
initConnectionData :: Hostname -> Port -> Text -> ConnectionType -> ConnectionPoolConfig -> IO ConnectionData Source #
mmCloseSession :: Session -> IO () Source #
mmLogin :: ConnectionData -> Login -> IO (Either LoginFailureException (Session, User)) Source #
Fire off a login attempt. Note: We get back more than just the auth token. We also get all the server-side configuration data for the user.
route: /api/v3/users/login
mmCreateDirect :: Session -> TeamId -> UserId -> IO Channel Source #
route: /api/v3/teams/{team_id}/channels/create_direct
mmCreateChannel :: Session -> TeamId -> MinChannel -> IO Channel Source #
route: /api/v3/teams/{team_id}/channels/create
mmCreateGroupChannel :: Session -> [UserId] -> IO Channel Source #
Create a group channel containing the specified users in addition to the user making the request.
mmCreateTeam :: Session -> TeamsCreate -> IO Team Source #
route: /api/v3/teams/create
mmDeleteChannel :: Session -> TeamId -> ChannelId -> IO () Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/delete
mmLeaveChannel :: Session -> TeamId -> ChannelId -> IO () Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/leave
mmJoinChannel :: Session -> TeamId -> ChannelId -> IO () Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/join
mmGetTeams :: Session -> IO (HashMap TeamId Team) Source #
Requires an authenticated user. Returns the full list of teams.
route: /api/v3/teams/all
mmGetChannels :: Session -> TeamId -> IO Channels Source #
Requires an authenticated user. Returns the full list of channels for a given team of which the user is a member
route: /api/v3/teams/{team_id}/channels/
mmGetAllChannelDataForUser :: Session -> TeamId -> UserId -> IO (Seq ChannelData) Source #
Get channel/user metadata in bulk.
mmGetAllChannelsWithDataForUser :: Session -> TeamId -> UserId -> IO (HashMap ChannelId ChannelWithData) Source #
mmGetMoreChannels :: Session -> TeamId -> Int -> Int -> IO Channels Source #
Requires an authenticated user. Returns the channels for a team of which the user is not already a member
route: /api/v3/teams/{team_id}/channels/more/{offset}/{limit}
mmGetChannel :: Session -> TeamId -> ChannelId -> IO ChannelWithData Source #
Requires an authenticated user. Returns the details of a specific channel.
route: /api/v3/teams/{team_id}/channels/{channel_id}
route: /api/v3/teams/{team_id}/channels/view
mmDeletePost :: Session -> TeamId -> ChannelId -> PostId -> IO () Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/{post_id}/delete
mmGetPost :: Session -> TeamId -> ChannelId -> PostId -> IO Posts Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/{post_id}/get
mmGetPosts :: Session -> TeamId -> ChannelId -> Int -> Int -> IO Posts Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/page/{offset}/{limit}
mmGetPostsSince :: Session -> TeamId -> ChannelId -> ServerTime -> IO Posts Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/since/{utc_time}
mmGetPostsBefore :: Session -> TeamId -> ChannelId -> PostId -> Int -> Int -> IO Posts Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/{post_id}/before/{offset}/{limit}
mmGetPostsAfter :: Session -> TeamId -> ChannelId -> PostId -> Int -> Int -> IO Posts Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/{post_id}/after/{offset}/{limit}
mmSearchPosts :: Session -> TeamId -> Text -> Bool -> IO Posts Source #
route: /api/v4/teams/{team_id}/posts/search
mmGetReactionsForPost :: Session -> TeamId -> ChannelId -> PostId -> IO [Reaction] Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/{post_id}/reactions
mmGetUsers :: Session -> Int -> Int -> IO (HashMap UserId User) Source #
route: /api/v3/users/{offset}/{limit}
mmGetTeamMembers :: Session -> TeamId -> IO (Seq TeamMember) Source #
route: /api/v3/teams/members/{team_id}
mmGetChannelMembers :: Session -> TeamId -> ChannelId -> Int -> Int -> IO (HashMap UserId User) Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/users/{offset}/{limit}
mmGetProfilesForDMList :: Session -> TeamId -> IO (HashMap UserId User) Source #
route: /api/v3/users/profiles_for_dm_list/{team_id}
mmGetProfiles :: Session -> TeamId -> Int -> Int -> IO (HashMap UserId User) Source #
route: /api/v3/teams/{team_id}/users/{offset}/{limit}
mmGetInitialLoad :: Session -> IO InitialLoad Source #
Fire off a login attempt. Note: We get back more than just the auth token. We also get all the server-side configuration data for the user.
route: /api/v3/users/initial_load
mmSetChannelHeader :: Session -> TeamId -> ChannelId -> Text -> IO Channel Source #
route: /api/v3/teams/{team_id}/channels/update_header
mmChannelAddUser :: Session -> TeamId -> ChannelId -> UserId -> IO ChannelData Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/add
mmChannelRemoveUser :: Session -> ChannelId -> UserId -> IO () Source #
Remove the specified user from the specified channel.
mmTeamAddUser :: Session -> TeamId -> UserId -> IO () Source #
route: /api/v3/teams/{team_id}/add_user_to_team
mmUsersCreate :: ConnectionData -> UsersCreate -> IO User Source #
route: /api/v3/users/create
mmUsersCreateWithSession :: Session -> UsersCreate -> IO User Source #
route: /api/v3/users/create
mmPost :: Session -> TeamId -> PendingPost -> IO Post Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/create
mmUpdatePost :: Session -> TeamId -> Post -> IO Post Source #
route: /api/v3/teams/{team_id}/channels/{channel_id}/posts/update
mmExecute :: Session -> TeamId -> MinCommand -> IO CommandResponse Source #
route: /api/v3/teams/{team_id}/commands/execute
mmGetConfig :: Session -> IO Value Source #
Get the system configuration. Requires administrative permission.
route: /api/v3/admin/config
mmGetClientConfig :: Session -> IO Value Source #
Get a subset of the server configuration needed by the client. Does not require administrative permission. The format query parameter is currently required with the value of "old".
route: /api/v4/config/client
mmSetPreferences :: Session -> UserId -> Seq Preference -> IO () Source #
mmSavePreferences :: Session -> Seq Preference -> IO () Source #
route: /api/v3/preferences/save
mmDeletePreferences :: Session -> Seq Preference -> IO () Source #
route: /api/v3/preferences/save
mmFlagPost :: Session -> UserId -> PostId -> IO () Source #
route: /api/v3/preferences/save
This is a convenience function for a particular use of
mmSavePreference
mmUnflagPost :: Session -> UserId -> PostId -> IO () Source #
route: /api/v3/preferences/save
This is a convenience function for a particular use of
mmSavePreference
mmGetMyPreferences :: Session -> IO (Seq Preference) Source #
mkPendingPost :: Text -> UserId -> ChannelId -> IO PendingPost Source #