| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Network.Mattermost.Types
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 #
Constructors
| ChannelUnread | |
Instances
| Eq ChannelUnread Source # | |
Defined in Network.Mattermost.Types Methods (==) :: ChannelUnread -> ChannelUnread -> Bool # (/=) :: ChannelUnread -> ChannelUnread -> Bool # | |
| Read ChannelUnread Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS ChannelUnread # readList :: ReadS [ChannelUnread] # | |
| Show ChannelUnread Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> ChannelUnread -> ShowS # show :: ChannelUnread -> String # showList :: [ChannelUnread] -> ShowS # | |
| ToJSON ChannelUnread Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: ChannelUnread -> Value # toEncoding :: ChannelUnread -> Encoding # toJSONList :: [ChannelUnread] -> Value # toEncodingList :: [ChannelUnread] -> Encoding # | |
| FromJSON ChannelUnread Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser ChannelUnread # parseJSONList :: Value -> Parser [ChannelUnread] # | |
data ChannelStats Source #
Constructors
| ChannelStats | |
Fields | |
Instances
| Eq ChannelStats Source # | |
Defined in Network.Mattermost.Types | |
| Read ChannelStats Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS ChannelStats # readList :: ReadS [ChannelStats] # | |
| Show ChannelStats Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> ChannelStats -> ShowS # show :: ChannelStats -> String # showList :: [ChannelStats] -> ShowS # | |
| ToJSON ChannelStats Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: ChannelStats -> Value # toEncoding :: ChannelStats -> Encoding # toJSONList :: [ChannelStats] -> Value # toEncodingList :: [ChannelStats] -> Encoding # | |
| FromJSON ChannelStats Source # | |
Defined in Network.Mattermost.Types | |
data InitialTeamData Source #
Constructors
| InitialTeamData | |
Fields
| |
Instances
| Eq InitialTeamData Source # | |
Defined in Network.Mattermost.Types Methods (==) :: InitialTeamData -> InitialTeamData -> Bool # (/=) :: InitialTeamData -> InitialTeamData -> Bool # | |
| Read InitialTeamData Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS InitialTeamData # readList :: ReadS [InitialTeamData] # | |
| Show InitialTeamData Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> InitialTeamData -> ShowS # show :: InitialTeamData -> String # showList :: [InitialTeamData] -> ShowS # | |
| ToJSON InitialTeamData Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: InitialTeamData -> Value # toEncoding :: InitialTeamData -> Encoding # toJSONList :: [InitialTeamData] -> Value # toEncodingList :: [InitialTeamData] -> Encoding # | |
| FromJSON InitialTeamData Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser InitialTeamData # parseJSONList :: Value -> Parser [InitialTeamData] # | |
data ChannelPatch Source #
Constructors
| ChannelPatch | |
Fields
| |
Instances
| Eq ChannelPatch Source # | |
Defined in Network.Mattermost.Types | |
| Read ChannelPatch Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS ChannelPatch # readList :: ReadS [ChannelPatch] # | |
| Show ChannelPatch Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> ChannelPatch -> ShowS # show :: ChannelPatch -> String # showList :: [ChannelPatch] -> ShowS # | |
| ToJSON ChannelPatch Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: ChannelPatch -> Value # toEncoding :: ChannelPatch -> Encoding # toJSONList :: [ChannelPatch] -> Value # toEncodingList :: [ChannelPatch] -> Encoding # | |
| FromJSON ChannelPatch Source # | |
Defined in Network.Mattermost.Types | |
data PostUpdate Source #
Constructors
| PostUpdate | |
Fields
| |
Instances
| Eq PostUpdate Source # | |
Defined in Network.Mattermost.Types | |
| Read PostUpdate Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS PostUpdate # readList :: ReadS [PostUpdate] # readPrec :: ReadPrec PostUpdate # readListPrec :: ReadPrec [PostUpdate] # | |
| Show PostUpdate Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> PostUpdate -> ShowS # show :: PostUpdate -> String # showList :: [PostUpdate] -> ShowS # | |
| ToJSON PostUpdate Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: PostUpdate -> Value # toEncoding :: PostUpdate -> Encoding # toJSONList :: [PostUpdate] -> Value # toEncodingList :: [PostUpdate] -> Encoding # | |
| FromJSON PostUpdate Source # | |
Defined in Network.Mattermost.Types | |
Constructors
| RawPost | |
Fields
| |
data UserSearch Source #
Constructors
| UserSearch | |
Fields
| |
Instances
| Eq UserSearch Source # | |
Defined in Network.Mattermost.Types | |
| Read UserSearch Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS UserSearch # readList :: ReadS [UserSearch] # readPrec :: ReadPrec UserSearch # readListPrec :: ReadPrec [UserSearch] # | |
| Show UserSearch Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> UserSearch -> ShowS # show :: UserSearch -> String # showList :: [UserSearch] -> ShowS # | |
| ToJSON UserSearch Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: UserSearch -> Value # toEncoding :: UserSearch -> Encoding # toJSONList :: [UserSearch] -> Value # toEncodingList :: [UserSearch] -> Encoding # | |
| FromJSON UserSearch Source # | |
Defined in Network.Mattermost.Types | |
Constructors
| Status | |
Fields | |
data ChannelMember Source #
Constructors
| ChannelMember | |
Instances
| Eq ChannelMember Source # | |
Defined in Network.Mattermost.Types Methods (==) :: ChannelMember -> ChannelMember -> Bool # (/=) :: ChannelMember -> ChannelMember -> Bool # | |
| Read ChannelMember Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS ChannelMember # readList :: ReadS [ChannelMember] # | |
| Show ChannelMember Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> ChannelMember -> ShowS # show :: ChannelMember -> String # showList :: [ChannelMember] -> ShowS # | |
| ToJSON ChannelMember Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: ChannelMember -> Value # toEncoding :: ChannelMember -> Encoding # toJSONList :: [ChannelMember] -> Value # toEncodingList :: [ChannelMember] -> Encoding # | |
| FromJSON ChannelMember Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser ChannelMember # parseJSONList :: Value -> Parser [ChannelMember] # | |
data MinChannelMember Source #
Constructors
| MinChannelMember | |
Instances
| Eq MinChannelMember Source # | |
Defined in Network.Mattermost.Types Methods (==) :: MinChannelMember -> MinChannelMember -> Bool # (/=) :: MinChannelMember -> MinChannelMember -> Bool # | |
| Read MinChannelMember Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS MinChannelMember # readList :: ReadS [MinChannelMember] # | |
| Show MinChannelMember Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> MinChannelMember -> ShowS # show :: MinChannelMember -> String # showList :: [MinChannelMember] -> ShowS # | |
| ToJSON MinChannelMember Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: MinChannelMember -> Value # toEncoding :: MinChannelMember -> Encoding # toJSONList :: [MinChannelMember] -> Value # toEncodingList :: [MinChannelMember] -> Encoding # | |
| FromJSON MinChannelMember Source # | |
Defined in Network.Mattermost.Types Methods 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 # | |
Defined in Network.Mattermost.Types Methods | |
| PrintfArg ReportId Source # | |
Defined in Network.Mattermost.Types | |
| IsId ReportId Source # | |
Instances
| Eq EmojiId Source # | |
| Ord EmojiId Source # | |
Defined in Network.Mattermost.Types | |
| 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 Methods | |
| PrintfArg EmojiId Source # | |
Defined in Network.Mattermost.Types | |
| 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 | |
| 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 | |
| IsId AppId Source # | |
Instances
| Eq TokenId Source # | |
| Ord TokenId Source # | |
Defined in Network.Mattermost.Types | |
| 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 Methods | |
| PrintfArg TokenId Source # | |
Defined in Network.Mattermost.Types | |
| 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 # | |
Defined in Network.Mattermost.Types Methods | |
| PrintfArg InviteId Source # | |
Defined in Network.Mattermost.Types | |
| 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 | |
| IsId HookId Source # | |
data FlaggedPost Source #
Constructors
| FlaggedPost | |
Fields | |
Instances
| Eq FlaggedPost Source # | |
Defined in Network.Mattermost.Types | |
| Read FlaggedPost Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS FlaggedPost # readList :: ReadS [FlaggedPost] # readPrec :: ReadPrec FlaggedPost # readListPrec :: ReadPrec [FlaggedPost] # | |
| Show FlaggedPost Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> FlaggedPost -> ShowS # show :: FlaggedPost -> String # showList :: [FlaggedPost] -> ShowS # | |
| ToJSON FlaggedPost Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: FlaggedPost -> Value # toEncoding :: FlaggedPost -> Encoding # toJSONList :: [FlaggedPost] -> Value # toEncodingList :: [FlaggedPost] -> Encoding # | |
data GroupChannelPreference Source #
Constructors
| GroupChannelPreference | |
Fields | |
Instances
| Eq GroupChannelPreference Source # | |
Defined in Network.Mattermost.Types Methods (==) :: GroupChannelPreference -> GroupChannelPreference -> Bool # (/=) :: GroupChannelPreference -> GroupChannelPreference -> Bool # | |
| Read GroupChannelPreference Source # | |
Defined in Network.Mattermost.Types | |
| Show GroupChannelPreference Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> GroupChannelPreference -> ShowS # show :: GroupChannelPreference -> String # showList :: [GroupChannelPreference] -> ShowS # | |
data Preference Source #
Constructors
| Preference | |
Instances
| Eq Preference Source # | |
Defined in Network.Mattermost.Types | |
| Read Preference Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS Preference # readList :: ReadS [Preference] # readPrec :: ReadPrec Preference # readListPrec :: ReadPrec [Preference] # | |
| Show Preference Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> Preference -> ShowS # show :: Preference -> String # showList :: [Preference] -> ShowS # | |
| ToJSON Preference Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: Preference -> Value # toEncoding :: Preference -> Encoding # toJSONList :: [Preference] -> Value # toEncodingList :: [Preference] -> Encoding # | |
| FromJSON Preference Source # | |
Defined in Network.Mattermost.Types | |
data PreferenceValue Source #
Constructors
| PreferenceValue | |
Fields | |
Instances
| Eq PreferenceValue Source # | |
Defined in Network.Mattermost.Types Methods (==) :: PreferenceValue -> PreferenceValue -> Bool # (/=) :: PreferenceValue -> PreferenceValue -> Bool # | |
| Read PreferenceValue Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS PreferenceValue # readList :: ReadS [PreferenceValue] # | |
| Show PreferenceValue Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> PreferenceValue -> ShowS # show :: PreferenceValue -> String # showList :: [PreferenceValue] -> ShowS # | |
| ToJSON PreferenceValue Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: PreferenceValue -> Value # toEncoding :: PreferenceValue -> Encoding # toJSONList :: [PreferenceValue] -> Value # toEncodingList :: [PreferenceValue] -> Encoding # | |
| FromJSON PreferenceValue Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser PreferenceValue # parseJSONList :: Value -> Parser [PreferenceValue] # | |
data PreferenceName Source #
Constructors
| PreferenceName | |
Fields | |
Instances
| Eq PreferenceName Source # | |
Defined in Network.Mattermost.Types Methods (==) :: PreferenceName -> PreferenceName -> Bool # (/=) :: PreferenceName -> PreferenceName -> Bool # | |
| Read PreferenceName Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS PreferenceName # readList :: ReadS [PreferenceName] # | |
| Show PreferenceName Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> PreferenceName -> ShowS # show :: PreferenceName -> String # showList :: [PreferenceName] -> ShowS # | |
| ToJSON PreferenceName Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: PreferenceName -> Value # toEncoding :: PreferenceName -> Encoding # toJSONList :: [PreferenceName] -> Value # toEncodingList :: [PreferenceName] -> Encoding # | |
| FromJSON PreferenceName Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser PreferenceName # parseJSONList :: Value -> Parser [PreferenceName] # | |
data PreferenceCategory Source #
Constructors
Instances
Constructors
| Reaction | |
Fields | |
data TeamsCreate Source #
Constructors
| TeamsCreate | |
Fields | |
Instances
| Eq TeamsCreate Source # | |
Defined in Network.Mattermost.Types | |
| Read TeamsCreate Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS TeamsCreate # readList :: ReadS [TeamsCreate] # readPrec :: ReadPrec TeamsCreate # readListPrec :: ReadPrec [TeamsCreate] # | |
| Show TeamsCreate Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> TeamsCreate -> ShowS # show :: TeamsCreate -> String # showList :: [TeamsCreate] -> ShowS # | |
| ToJSON TeamsCreate Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: TeamsCreate -> Value # toEncoding :: TeamsCreate -> Encoding # toJSONList :: [TeamsCreate] -> Value # toEncodingList :: [TeamsCreate] -> Encoding # | |
data UsersCreate Source #
Constructors
| UsersCreate | |
Fields | |
Instances
| Eq UsersCreate Source # | |
Defined in Network.Mattermost.Types | |
| Read UsersCreate Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS UsersCreate # readList :: ReadS [UsersCreate] # readPrec :: ReadPrec UsersCreate # readListPrec :: ReadPrec [UsersCreate] # | |
| Show UsersCreate Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> UsersCreate -> ShowS # show :: UsersCreate -> String # showList :: [UsersCreate] -> ShowS # | |
| ToJSON UsersCreate Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: UsersCreate -> Value # toEncoding :: UsersCreate -> Encoding # toJSONList :: [UsersCreate] -> Value # toEncodingList :: [UsersCreate] -> Encoding # | |
data CommandResponse Source #
Constructors
| CommandResponse | |
Instances
| Eq CommandResponse Source # | |
Defined in Network.Mattermost.Types Methods (==) :: CommandResponse -> CommandResponse -> Bool # (/=) :: CommandResponse -> CommandResponse -> Bool # | |
| Read CommandResponse Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS CommandResponse # readList :: ReadS [CommandResponse] # | |
| Show CommandResponse Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> CommandResponse -> ShowS # show :: CommandResponse -> String # showList :: [CommandResponse] -> ShowS # | |
| FromJSON CommandResponse Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser CommandResponse # parseJSONList :: Value -> Parser [CommandResponse] # | |
data CommandResponseType Source #
Constructors
| CommandResponseInChannel | |
| CommandResponseEphemeral |
Instances
| Eq CommandResponseType Source # | |
Defined in Network.Mattermost.Types Methods (==) :: CommandResponseType -> CommandResponseType -> Bool # (/=) :: CommandResponseType -> CommandResponseType -> Bool # | |
| Read CommandResponseType Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS CommandResponseType # readList :: ReadS [CommandResponseType] # | |
| Show CommandResponseType Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> CommandResponseType -> ShowS # show :: CommandResponseType -> String # showList :: [CommandResponseType] -> ShowS # | |
| FromJSON CommandResponseType Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser CommandResponseType # parseJSONList :: Value -> Parser [CommandResponseType] # | |
Instances
| Eq CommandId Source # | |
| Ord CommandId Source # | |
| 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 # | |
Defined in Network.Mattermost.Types Methods | |
| PrintfArg CommandId Source # | |
Defined in Network.Mattermost.Types | |
| IsId CommandId Source # | |
| HasId Command CommandId Source # | |
Constructors
data MinCommand Source #
Constructors
| MinCommand | |
Fields | |
Instances
| Eq MinCommand Source # | |
Defined in Network.Mattermost.Types | |
| Read MinCommand Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS MinCommand # readList :: ReadS [MinCommand] # readPrec :: ReadPrec MinCommand # readListPrec :: ReadPrec [MinCommand] # | |
| Show MinCommand Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> MinCommand -> ShowS # show :: MinCommand -> String # showList :: [MinCommand] -> ShowS # | |
| ToJSON MinCommand Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: MinCommand -> Value # toEncoding :: MinCommand -> Encoding # toJSONList :: [MinCommand] -> Value # toEncodingList :: [MinCommand] -> Encoding # | |
Constructors
| Posts | |
Fields
| |
Constructors
| FileInfo | |
Fields
| |
newtype PendingPostId Source #
Instances
data PendingPost Source #
Constructors
| PendingPost | |
Instances
| Eq PendingPost Source # | |
Defined in Network.Mattermost.Types | |
| Read PendingPost Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS PendingPost # readList :: ReadS [PendingPost] # readPrec :: ReadPrec PendingPost # readListPrec :: ReadPrec [PendingPost] # | |
| Show PendingPost Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> PendingPost -> ShowS # show :: PendingPost -> String # showList :: [PendingPost] -> ShowS # | |
| ToJSON PendingPost Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: PendingPost -> Value # toEncoding :: PendingPost -> Encoding # toJSONList :: [PendingPost] -> Value # toEncodingList :: [PendingPost] -> Encoding # | |
| HasId PendingPost PendingPostId Source # | |
Defined in Network.Mattermost.Types Methods getId :: PendingPost -> PendingPostId Source # | |
Constructors
| Post | |
Fields
| |
Constructors
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 | |
| 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 | |
| IsId PostId Source # | |
| HasId Post PostId Source # | |
Constructors
| PostProps | |
data PostPropAttachment Source #
Constructors
| PostPropAttachment | |
Fields
| |
Instances
data PostPropAttachmentField Source #
Instances
| Eq PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types Methods (==) :: PostPropAttachmentField -> PostPropAttachmentField -> Bool # (/=) :: PostPropAttachmentField -> PostPropAttachmentField -> Bool # | |
| Read PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types | |
| Show PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> PostPropAttachmentField -> ShowS # show :: PostPropAttachmentField -> String # showList :: [PostPropAttachmentField] -> ShowS # | |
| FromJSON PostPropAttachmentField Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser PostPropAttachmentField # parseJSONList :: Value -> Parser [PostPropAttachmentField] # | |
Constructors
| User | |
Fields
| |
data InitialLoad Source #
Constructors
| InitialLoad | |
Fields | |
Instances
| Eq InitialLoad Source # | |
Defined in Network.Mattermost.Types | |
| Show InitialLoad Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> InitialLoad -> ShowS # show :: InitialLoad -> String # showList :: [InitialLoad] -> ShowS # | |
| FromJSON InitialLoad Source # | |
Defined in Network.Mattermost.Types | |
Instances
| Eq UserParam Source # | |
| Ord UserParam Source # | |
| Read UserParam Source # | |
| Show UserParam Source # | |
| PrintfArg UserParam Source # | |
Defined in Network.Mattermost.Types | |
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 | |
| IsId UserId Source # | |
| HasId User UserId Source # | |
data MinChannel Source #
Constructors
| MinChannel | |
Fields | |
Instances
| Eq MinChannel Source # | |
Defined in Network.Mattermost.Types | |
| Read MinChannel Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS MinChannel # readList :: ReadS [MinChannel] # readPrec :: ReadPrec MinChannel # readListPrec :: ReadPrec [MinChannel] # | |
| Show MinChannel Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> MinChannel -> ShowS # show :: MinChannel -> String # showList :: [MinChannel] -> ShowS # | |
| ToJSON MinChannel Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: MinChannel -> Value # toEncoding :: MinChannel -> Encoding # toJSONList :: [MinChannel] -> Value # toEncodingList :: [MinChannel] -> Encoding # | |
data ChannelWithData Source #
Constructors
| ChannelWithData Channel ChannelData |
Instances
| Eq ChannelWithData Source # | |
Defined in Network.Mattermost.Types Methods (==) :: ChannelWithData -> ChannelWithData -> Bool # (/=) :: ChannelWithData -> ChannelWithData -> Bool # | |
| Read ChannelWithData Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS ChannelWithData # readList :: ReadS [ChannelWithData] # | |
| Show ChannelWithData Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> ChannelWithData -> ShowS # show :: ChannelWithData -> String # showList :: [ChannelWithData] -> ShowS # | |
| FromJSON ChannelWithData Source # | |
Defined in Network.Mattermost.Types Methods parseJSON :: Value -> Parser ChannelWithData # parseJSONList :: Value -> Parser [ChannelWithData] # | |
data ChannelData Source #
Constructors
| ChannelData | |
Instances
| Eq ChannelData Source # | |
Defined in Network.Mattermost.Types | |
| Read ChannelData Source # | |
Defined in Network.Mattermost.Types Methods readsPrec :: Int -> ReadS ChannelData # readList :: ReadS [ChannelData] # readPrec :: ReadPrec ChannelData # readListPrec :: ReadPrec [ChannelData] # | |
| Show ChannelData Source # | |
Defined in Network.Mattermost.Types Methods showsPrec :: Int -> ChannelData -> ShowS # show :: ChannelData -> String # showList :: [ChannelData] -> ShowS # | |
| FromJSON ChannelData Source # | |
Defined in Network.Mattermost.Types | |
| HasId ChannelData ChannelId Source # | |
Defined in Network.Mattermost.Types Methods getId :: ChannelData -> ChannelId Source # | |
newtype SingleChannel Source #
Instances
Constructors
Instances
| Eq ChannelId Source # | |
| Ord ChannelId Source # | |
| 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 # | |
Defined in Network.Mattermost.Types Methods | |
| PrintfArg ChannelId Source # | |
Defined in Network.Mattermost.Types | |
| IsId ChannelId Source # | |
| HasId ChannelData ChannelId Source # | |
Defined in Network.Mattermost.Types Methods getId :: ChannelData -> ChannelId Source # | |
| HasId Channel ChannelId Source # | |
newtype BoolString Source #
Constructors
| BoolString | |
Fields | |
Instances
| ToJSON BoolString Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: BoolString -> Value # toEncoding :: BoolString -> Encoding # toJSONList :: [BoolString] -> Value # toEncodingList :: [BoolString] -> Encoding # | |
| FromJSON BoolString Source # | |
Defined in Network.Mattermost.Types | |
data ChannelNotifyProps Source #
Constructors
| ChannelNotifyProps | |
Instances
data UserNotifyProps Source #
Constructors
| UserNotifyProps | |
Instances
data NotifyOption Source #
Constructors
| NotifyOptionAll | |
| NotifyOptionMention | |
| NotifyOptionNone |
Instances
data WithDefault a Source #
Instances
data TeamMember Source #
Constructors
| TeamMember | |
Fields | |
Instances
Constructors
| Team | |
Fields
| |
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 | |
| 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 Methods getId :: PendingPost -> PendingPostId Source # | |
| HasId Post PostId Source # | |
| HasId User UserId Source # | |
| HasId ChannelData ChannelId Source # | |
Defined in Network.Mattermost.Types Methods getId :: ChannelData -> ChannelId Source # | |
| HasId Channel ChannelId Source # | |
| HasId Team TeamId Source # | |
| HasId Id Id Source # | |
Instances
data SearchPosts Source #
Constructors
| SearchPosts | |
Fields | |
Instances
| ToJSON SearchPosts Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: SearchPosts -> Value # toEncoding :: SearchPosts -> Encoding # toJSONList :: [SearchPosts] -> Value # toEncodingList :: [SearchPosts] -> Encoding # | |
data SetChannelHeader Source #
Constructors
| SetChannelHeader | |
Fields | |
Instances
| ToJSON SetChannelHeader Source # | |
Defined in Network.Mattermost.Types Methods toJSON :: SetChannelHeader -> Value # toEncoding :: SetChannelHeader -> Encoding # toJSONList :: [SetChannelHeader] -> Value # toEncodingList :: [SetChannelHeader] -> Encoding # | |
data ConnectionPoolConfig Source #
Constructors
| ConnectionPoolConfig | |
Fields | |
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 #