Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data ChannelUnread = ChannelUnread {}
- data ChannelStats = ChannelStats {}
- data InitialTeamData = InitialTeamData {}
- data ChannelPatch = ChannelPatch {}
- data PostUpdate = PostUpdate {}
- data RawPost = RawPost {}
- data UserSearch = UserSearch {}
- data Status = Status {}
- data ChannelMember = ChannelMember {}
- data MinChannelMember = MinChannelMember {}
- newtype ReportId = RI {}
- newtype EmojiId = EI {}
- newtype JobId = JI {}
- newtype AppId = AI {}
- newtype TokenId = TkI {}
- newtype InviteId = II {}
- newtype HookId = HI {}
- data FlaggedPost = FlaggedPost {}
- data GroupChannelPreference = GroupChannelPreference {}
- data Preference = Preference {}
- data PreferenceValue = PreferenceValue {}
- data PreferenceName = PreferenceName {}
- data PreferenceCategory
- = PreferenceCategoryDirectChannelShow
- | PreferenceCategoryGroupChannelShow
- | PreferenceCategoryTutorialStep
- | PreferenceCategoryAdvancedSettings
- | PreferenceCategoryFlaggedPost
- | PreferenceCategoryDisplaySettings
- | PreferenceCategoryTheme
- | PreferenceCategoryAuthorizedOAuthApp
- | PreferenceCategoryNotifications
- | PreferenceCategoryLast
- | PreferenceCategoryOther Text
- data Reaction = Reaction {}
- data TeamsCreate = TeamsCreate {}
- data UsersCreate = UsersCreate {}
- data CommandResponse = CommandResponse {}
- data CommandResponseType
- newtype CommandId = CmdI {}
- data Command = Command {
- commandId :: CommandId
- commandToken :: Token
- commandCreateAt :: ServerTime
- commandUpdateAt :: ServerTime
- commandDeleteAt :: ServerTime
- commandCreatorId :: UserId
- commandTeamId :: TeamId
- commandTrigger :: Text
- commandMethod :: Text
- commandUsername :: Text
- commandIconURL :: Text
- commandAutoComplete :: Bool
- commandAutoCompleteDesc :: Text
- commandAutoCompleteHint :: Text
- commandDisplayName :: Text
- commandDescription :: Text
- commandURL :: Text
- data MinCommand = MinCommand {}
- data Posts = Posts {}
- 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
- newtype PendingPostId = PPI {}
- data PendingPost = PendingPost {}
- 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
- data PostType
- newtype FileId = FI {}
- newtype PostId = PI {}
- data PostProps = PostProps {}
- data PostPropAttachment = PostPropAttachment {
- ppaId :: Int
- ppaFallback :: Text
- ppaColor :: Text
- ppaPretext :: Text
- ppaAuthorName :: Text
- ppaAuthorLink :: Text
- ppaAuthorIcon :: Text
- ppaTitle :: Text
- ppaTitleLink :: Text
- ppaText :: Text
- ppaFields :: Seq PostPropAttachmentField
- ppaImageURL :: Text
- ppaThumbURL :: Text
- ppaFooter :: Text
- ppaFooterIcon :: Text
- data PostPropAttachmentField = PostPropAttachmentField {}
- data User = User {
- userId :: UserId
- userCreateAt :: ServerTime
- userUpdateAt :: ServerTime
- userDeleteAt :: ServerTime
- userUsername :: Text
- userAuthData :: 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
- data InitialLoad = InitialLoad {}
- data UserParam
- newtype UserId = UI {}
- data MinChannel = MinChannel {}
- type Channels = Seq Channel
- data ChannelWithData = ChannelWithData Channel ChannelData
- data ChannelData = ChannelData {}
- newtype SingleChannel = SC Channel
- 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
- newtype ChannelId = CI {}
- newtype BoolString = BoolString {}
- data ChannelNotifyProps = ChannelNotifyProps {}
- data UserNotifyProps = UserNotifyProps {}
- data NotifyOption
- data WithDefault a
- data TeamMember = TeamMember {}
- data Team = Team {}
- newtype TeamId = TI {}
- newtype Id = Id {}
- class HasId x y | x -> y where
- getId :: x -> y
- class IsId x where
- data Type
- data SearchPosts = SearchPosts {}
- data SetChannelHeader = SetChannelHeader {}
- data Login = Login {}
- data Session = Session {}
- data ConnectionPoolConfig = ConnectionPoolConfig {}
- newtype UserText = UserText Text
- unsafeUserText :: UserText -> Text
- runLogger :: ConnectionData -> String -> LogEventType -> IO ()
- runLoggerS :: Session -> String -> LogEventType -> IO ()
- maybeFail :: Parser a -> Parser (Maybe a)
- mkConnectionData :: Hostname -> Port -> Pool MMConn -> ConnectionContext -> ConnectionData
- mkConnectionDataInsecure :: Hostname -> Port -> Pool MMConn -> ConnectionContext -> ConnectionData
- createPool :: Hostname -> Port -> ConnectionContext -> ConnectionPoolConfig -> Bool -> IO (Pool MMConn)
- initConnectionData :: Hostname -> Port -> ConnectionPoolConfig -> IO ConnectionData
- initConnectionDataInsecure :: Hostname -> Port -> ConnectionPoolConfig -> IO ConnectionData
- destroyConnectionData :: ConnectionData -> IO ()
- withLogger :: ConnectionData -> Logger -> ConnectionData
- noLogger :: ConnectionData -> ConnectionData
- defaultConnectionPoolConfig :: ConnectionPoolConfig
- idString :: IsId x => x -> Text
- emptyUserNotifyProps :: UserNotifyProps
- emptyChannelNotifyProps :: ChannelNotifyProps
- userParamString :: UserParam -> Text
- emptyPostProps :: PostProps
- urlForFile :: FileId -> Text
- mkPendingPost :: Text -> UserId -> ChannelId -> IO PendingPost
- timeFromServer :: Integer -> ServerTime
- timeToServer :: ServerTime -> Int
- preferenceToGroupChannelPreference :: Preference -> Maybe GroupChannelPreference
- preferenceToFlaggedPost :: Preference -> Maybe FlaggedPost
- rawPost :: Text -> ChannelId -> RawPost
- postUpdateBody :: Text -> PostUpdate
- defaultChannelPatch :: ChannelPatch
- module Network.Mattermost.Types.Base
Documentation
data ChannelUnread Source #
Instances
Eq ChannelUnread Source # | |
Defined in Network.Mattermost.Types (==) :: ChannelUnread -> ChannelUnread -> Bool # (/=) :: ChannelUnread -> ChannelUnread -> Bool # | |
Read ChannelUnread Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS ChannelUnread # readList :: ReadS [ChannelUnread] # | |
Show ChannelUnread Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> ChannelUnread -> ShowS # show :: ChannelUnread -> String # showList :: [ChannelUnread] -> ShowS # | |
ToJSON ChannelUnread Source # | |
Defined in Network.Mattermost.Types toJSON :: ChannelUnread -> Value # toEncoding :: ChannelUnread -> Encoding # toJSONList :: [ChannelUnread] -> Value # toEncodingList :: [ChannelUnread] -> Encoding # | |
FromJSON ChannelUnread Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser ChannelUnread # parseJSONList :: Value -> Parser [ChannelUnread] # |
data ChannelStats Source #
Instances
Eq ChannelStats Source # | |
Defined in Network.Mattermost.Types (==) :: ChannelStats -> ChannelStats -> Bool # (/=) :: ChannelStats -> ChannelStats -> Bool # | |
Read ChannelStats Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS ChannelStats # readList :: ReadS [ChannelStats] # | |
Show ChannelStats Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> ChannelStats -> ShowS # show :: ChannelStats -> String # showList :: [ChannelStats] -> ShowS # | |
ToJSON ChannelStats Source # | |
Defined in Network.Mattermost.Types toJSON :: ChannelStats -> Value # toEncoding :: ChannelStats -> Encoding # toJSONList :: [ChannelStats] -> Value # toEncodingList :: [ChannelStats] -> Encoding # | |
FromJSON ChannelStats Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser ChannelStats # parseJSONList :: Value -> Parser [ChannelStats] # |
data InitialTeamData Source #
InitialTeamData | |
|
Instances
Eq InitialTeamData Source # | |
Defined in Network.Mattermost.Types (==) :: InitialTeamData -> InitialTeamData -> Bool # (/=) :: InitialTeamData -> InitialTeamData -> Bool # | |
Read InitialTeamData Source # | |
Defined in Network.Mattermost.Types | |
Show InitialTeamData Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> InitialTeamData -> ShowS # show :: InitialTeamData -> String # showList :: [InitialTeamData] -> ShowS # | |
ToJSON InitialTeamData Source # | |
Defined in Network.Mattermost.Types toJSON :: InitialTeamData -> Value # toEncoding :: InitialTeamData -> Encoding # toJSONList :: [InitialTeamData] -> Value # toEncodingList :: [InitialTeamData] -> Encoding # | |
FromJSON InitialTeamData Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser InitialTeamData # parseJSONList :: Value -> Parser [InitialTeamData] # |
data ChannelPatch Source #
ChannelPatch | |
|
Instances
Eq ChannelPatch Source # | |
Defined in Network.Mattermost.Types (==) :: ChannelPatch -> ChannelPatch -> Bool # (/=) :: ChannelPatch -> ChannelPatch -> Bool # | |
Read ChannelPatch Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS ChannelPatch # readList :: ReadS [ChannelPatch] # | |
Show ChannelPatch Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> ChannelPatch -> ShowS # show :: ChannelPatch -> String # showList :: [ChannelPatch] -> ShowS # | |
ToJSON ChannelPatch Source # | |
Defined in Network.Mattermost.Types toJSON :: ChannelPatch -> Value # toEncoding :: ChannelPatch -> Encoding # toJSONList :: [ChannelPatch] -> Value # toEncodingList :: [ChannelPatch] -> Encoding # | |
FromJSON ChannelPatch Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser ChannelPatch # parseJSONList :: Value -> Parser [ChannelPatch] # |
data PostUpdate Source #
PostUpdate | |
|
Instances
Eq PostUpdate Source # | |
Defined in Network.Mattermost.Types (==) :: PostUpdate -> PostUpdate -> Bool # (/=) :: PostUpdate -> PostUpdate -> Bool # | |
Read PostUpdate Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS PostUpdate # readList :: ReadS [PostUpdate] # readPrec :: ReadPrec PostUpdate # readListPrec :: ReadPrec [PostUpdate] # | |
Show PostUpdate Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PostUpdate -> ShowS # show :: PostUpdate -> String # showList :: [PostUpdate] -> ShowS # | |
ToJSON PostUpdate Source # | |
Defined in Network.Mattermost.Types toJSON :: PostUpdate -> Value # toEncoding :: PostUpdate -> Encoding # toJSONList :: [PostUpdate] -> Value # toEncodingList :: [PostUpdate] -> Encoding # | |
FromJSON PostUpdate Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser PostUpdate # parseJSONList :: Value -> Parser [PostUpdate] # |
RawPost | |
|
data UserSearch Source #
UserSearch | |
|
Instances
Eq UserSearch Source # | |
Defined in Network.Mattermost.Types (==) :: UserSearch -> UserSearch -> Bool # (/=) :: UserSearch -> UserSearch -> Bool # | |
Read UserSearch Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS UserSearch # readList :: ReadS [UserSearch] # readPrec :: ReadPrec UserSearch # readListPrec :: ReadPrec [UserSearch] # | |
Show UserSearch Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> UserSearch -> ShowS # show :: UserSearch -> String # showList :: [UserSearch] -> ShowS # | |
ToJSON UserSearch Source # | |
Defined in Network.Mattermost.Types toJSON :: UserSearch -> Value # toEncoding :: UserSearch -> Encoding # toJSONList :: [UserSearch] -> Value # toEncodingList :: [UserSearch] -> Encoding # | |
FromJSON UserSearch Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser UserSearch # parseJSONList :: Value -> Parser [UserSearch] # |
data ChannelMember Source #
Instances
Eq ChannelMember Source # | |
Defined in Network.Mattermost.Types (==) :: ChannelMember -> ChannelMember -> Bool # (/=) :: ChannelMember -> ChannelMember -> Bool # | |
Read ChannelMember Source # | |
Defined in Network.Mattermost.Types readsPrec :: Int -> ReadS ChannelMember # readList :: ReadS [ChannelMember] # | |
Show ChannelMember Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> ChannelMember -> ShowS # show :: ChannelMember -> String # showList :: [ChannelMember] -> ShowS # | |
ToJSON ChannelMember Source # | |
Defined in Network.Mattermost.Types toJSON :: ChannelMember -> Value # toEncoding :: ChannelMember -> Encoding # toJSONList :: [ChannelMember] -> Value # toEncodingList :: [ChannelMember] -> Encoding # | |
FromJSON ChannelMember Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser ChannelMember # parseJSONList :: Value -> Parser [ChannelMember] # |
data MinChannelMember Source #
Instances
Eq MinChannelMember Source # | |
Defined in Network.Mattermost.Types (==) :: MinChannelMember -> MinChannelMember -> Bool # (/=) :: MinChannelMember -> MinChannelMember -> Bool # | |
Read MinChannelMember Source # | |
Defined in Network.Mattermost.Types | |
Show MinChannelMember Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> MinChannelMember -> ShowS # show :: MinChannelMember -> String # showList :: [MinChannelMember] -> ShowS # | |
ToJSON MinChannelMember Source # | |
Defined in Network.Mattermost.Types toJSON :: MinChannelMember -> Value # toEncoding :: MinChannelMember -> Encoding # toJSONList :: [MinChannelMember] -> Value # toEncodingList :: [MinChannelMember] -> Encoding # | |
FromJSON MinChannelMember Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser MinChannelMember # parseJSONList :: Value -> Parser [MinChannelMember] # |
Instances
Eq ReportId Source # | |
Ord ReportId Source # | |
Defined in Network.Mattermost.Types | |
Read ReportId Source # | |
Show ReportId Source # | |
Hashable ReportId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON ReportId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey ReportId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON ReportId Source # | |
FromJSONKey ReportId Source # | |
PrintfArg ReportId Source # | |
Defined in Network.Mattermost.Types formatArg :: ReportId -> FieldFormatter # parseFormat :: ReportId -> ModifierParser # | |
IsId ReportId Source # | |
Instances
Eq EmojiId Source # | |
Ord EmojiId Source # | |
Read EmojiId Source # | |
Show EmojiId Source # | |
Hashable EmojiId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON EmojiId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey EmojiId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON EmojiId Source # | |
FromJSONKey EmojiId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg EmojiId Source # | |
Defined in Network.Mattermost.Types formatArg :: EmojiId -> FieldFormatter # parseFormat :: EmojiId -> ModifierParser # | |
IsId EmojiId Source # | |
Instances
Eq JobId Source # | |
Ord JobId Source # | |
Read JobId Source # | |
Show JobId Source # | |
Hashable JobId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON JobId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey JobId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON JobId Source # | |
FromJSONKey JobId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg JobId Source # | |
Defined in Network.Mattermost.Types formatArg :: JobId -> FieldFormatter # parseFormat :: JobId -> ModifierParser # | |
IsId JobId Source # | |
Instances
Eq AppId Source # | |
Ord AppId Source # | |
Read AppId Source # | |
Show AppId Source # | |
Hashable AppId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON AppId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey AppId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON AppId Source # | |
FromJSONKey AppId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg AppId Source # | |
Defined in Network.Mattermost.Types formatArg :: AppId -> FieldFormatter # parseFormat :: AppId -> ModifierParser # | |
IsId AppId Source # | |
Instances
Eq TokenId Source # | |
Ord TokenId Source # | |
Read TokenId Source # | |
Show TokenId Source # | |
Hashable TokenId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON TokenId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey TokenId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON TokenId Source # | |
FromJSONKey TokenId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg TokenId Source # | |
Defined in Network.Mattermost.Types formatArg :: TokenId -> FieldFormatter # parseFormat :: TokenId -> ModifierParser # | |
IsId TokenId Source # | |
Instances
Eq InviteId Source # | |
Ord InviteId Source # | |
Defined in Network.Mattermost.Types | |
Read InviteId Source # | |
Show InviteId Source # | |
Hashable InviteId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON InviteId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey InviteId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON InviteId Source # | |
FromJSONKey InviteId Source # | |
PrintfArg InviteId Source # | |
Defined in Network.Mattermost.Types formatArg :: InviteId -> FieldFormatter # parseFormat :: InviteId -> ModifierParser # | |
IsId InviteId Source # | |
Instances
Eq HookId Source # | |
Ord HookId Source # | |
Read HookId Source # | |
Show HookId Source # | |
Hashable HookId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON HookId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey HookId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON HookId Source # | |
FromJSONKey HookId Source # | |
Defined in Network.Mattermost.Types | |
PrintfArg HookId Source # | |
Defined in Network.Mattermost.Types formatArg :: HookId -> FieldFormatter # parseFormat :: HookId -> ModifierParser # | |
IsId HookId Source # | |
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 # |
data GroupChannelPreference Source #
Instances
Eq GroupChannelPreference Source # | |
Defined in Network.Mattermost.Types | |
Read GroupChannelPreference Source # | |
Show GroupChannelPreference Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> GroupChannelPreference -> ShowS # show :: GroupChannelPreference -> String # showList :: [GroupChannelPreference] -> ShowS # |
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 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 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 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 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 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 # |
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] # |
Instances
Eq CommandId Source # | |
Ord CommandId Source # | |
Defined in Network.Mattermost.Types | |
Read CommandId Source # | |
Show CommandId Source # | |
Hashable CommandId Source # | |
Defined in Network.Mattermost.Types | |
ToJSON CommandId Source # | |
Defined in Network.Mattermost.Types | |
ToJSONKey CommandId Source # | |
Defined in Network.Mattermost.Types | |
FromJSON CommandId Source # | |
FromJSONKey CommandId Source # | |
PrintfArg CommandId Source # | |
Defined in Network.Mattermost.Types formatArg :: CommandId -> FieldFormatter # parseFormat :: CommandId -> ModifierParser # | |
IsId CommandId Source # | |
HasId Command CommandId Source # | |
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 # |
Posts | |
|
newtype PendingPostId Source #
Instances
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 # |
Post | |
|
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 # | |
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 # | |
data PostPropAttachment Source #
PostPropAttachment | |
|
Instances
Eq PostPropAttachment Source # | |
Defined in Network.Mattermost.Types (==) :: PostPropAttachment -> PostPropAttachment -> Bool # (/=) :: PostPropAttachment -> PostPropAttachment -> Bool # | |
Read PostPropAttachment Source # | |
Defined in Network.Mattermost.Types | |
Show PostPropAttachment Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PostPropAttachment -> ShowS # show :: PostPropAttachment -> String # showList :: [PostPropAttachment] -> ShowS # | |
ToJSON PostPropAttachment Source # | |
Defined in Network.Mattermost.Types toJSON :: PostPropAttachment -> Value # toEncoding :: PostPropAttachment -> Encoding # toJSONList :: [PostPropAttachment] -> Value # toEncodingList :: [PostPropAttachment] -> Encoding # | |
FromJSON PostPropAttachment Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser PostPropAttachment # parseJSONList :: Value -> Parser [PostPropAttachment] # |
data PostPropAttachmentField Source #
Instances
Eq PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types | |
Read PostPropAttachmentField Source # | |
Show PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types showsPrec :: Int -> PostPropAttachmentField -> ShowS # show :: PostPropAttachmentField -> String # showList :: [PostPropAttachmentField] -> ShowS # | |
FromJSON PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types |
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] # |
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 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 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 # |
newtype SingleChannel Source #
Instances
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 # | |
newtype BoolString Source #
Instances
ToJSON BoolString Source # | |
Defined in Network.Mattermost.Types toJSON :: BoolString -> Value # toEncoding :: BoolString -> Encoding # toJSONList :: [BoolString] -> Value # toEncodingList :: [BoolString] -> Encoding # | |
FromJSON BoolString Source # | |
Defined in Network.Mattermost.Types parseJSON :: Value -> Parser BoolString # parseJSONList :: Value -> Parser [BoolString] # |
data ChannelNotifyProps Source #
Instances
data UserNotifyProps Source #
Instances
data NotifyOption Source #
Instances
data WithDefault a Source #
Instances
data TeamMember Source #
Instances
Team | |
|
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 # | |
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 # | |
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 # | |
Instances
IsId ReportId Source # | |
IsId EmojiId Source # | |
IsId JobId Source # | |
IsId AppId Source # | |
IsId TokenId Source # | |
IsId InviteId Source # | |
IsId HookId Source # | |
IsId CommandId Source # | |
IsId PendingPostId Source # | |
Defined in Network.Mattermost.Types toId :: PendingPostId -> Id Source # fromId :: Id -> PendingPostId Source # | |
IsId FileId Source # | |
IsId PostId Source # | |
IsId UserId Source # | |
IsId ChannelId Source # | |
IsId TeamId Source # | |
IsId Id Source # | |
data SearchPosts Source #
Instances
ToJSON SearchPosts Source # | |
Defined in Network.Mattermost.Types toJSON :: SearchPosts -> Value # toEncoding :: SearchPosts -> Encoding # toJSONList :: [SearchPosts] -> Value # toEncodingList :: [SearchPosts] -> Encoding # |
data SetChannelHeader Source #
Instances
ToJSON SetChannelHeader Source # | |
Defined in Network.Mattermost.Types toJSON :: SetChannelHeader -> Value # toEncoding :: SetChannelHeader -> Encoding # toJSONList :: [SetChannelHeader] -> Value # toEncodingList :: [SetChannelHeader] -> Encoding # |
data ConnectionPoolConfig Source #
unsafeUserText :: UserText -> Text Source #
runLogger :: ConnectionData -> String -> LogEventType -> IO () Source #
runLoggerS :: Session -> String -> LogEventType -> IO () Source #
mkConnectionData :: Hostname -> Port -> Pool MMConn -> ConnectionContext -> ConnectionData Source #
Creates a structure representing a TLS connection to the server.
mkConnectionDataInsecure :: Hostname -> Port -> Pool MMConn -> ConnectionContext -> ConnectionData Source #
Plaintext HTTP instead of a TLS connection.
createPool :: Hostname -> Port -> ConnectionContext -> ConnectionPoolConfig -> Bool -> IO (Pool MMConn) Source #
initConnectionData :: Hostname -> Port -> ConnectionPoolConfig -> IO ConnectionData Source #
initConnectionDataInsecure :: Hostname -> Port -> ConnectionPoolConfig -> IO ConnectionData Source #
destroyConnectionData :: ConnectionData -> IO () Source #
withLogger :: ConnectionData -> Logger -> ConnectionData Source #
userParamString :: UserParam -> Text Source #
urlForFile :: FileId -> Text Source #
mkPendingPost :: Text -> UserId -> ChannelId -> IO PendingPost Source #
timeFromServer :: Integer -> ServerTime Source #
timeToServer :: ServerTime -> Int Source #
preferenceToGroupChannelPreference :: Preference -> Maybe GroupChannelPreference Source #
Attempt to expose a Preference
as a FlaggedPost
preferenceToFlaggedPost :: Preference -> Maybe FlaggedPost Source #
Attempt to expose a Preference
as a FlaggedPost
postUpdateBody :: Text -> PostUpdate Source #