| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.Mattermost.Types
Contents
- runLogger :: ConnectionData -> String -> LogEventType -> IO ()
- runLoggerS :: Session -> String -> LogEventType -> IO ()
- maybeFail :: Parser a -> Parser (Maybe a)
- mkConnectionData :: Hostname -> Port -> ConnectionContext -> ConnectionData
- mkConnectionDataInsecure :: Hostname -> Port -> ConnectionContext -> ConnectionData
- initConnectionData :: Hostname -> Port -> IO ConnectionData
- initConnectionDataInsecure :: Hostname -> Port -> IO ConnectionData
- withLogger :: ConnectionData -> Logger -> ConnectionData
- noLogger :: ConnectionData -> ConnectionData
- data Session = Session {}
- mkSession :: ConnectionData -> Token -> Session
- data Login = Login {}
- data SetChannelHeader = SetChannelHeader {}
- data SearchPosts = SearchPosts {}
- data Type
- class IsId x where
- class HasId x y | x -> y where
- newtype Id = Id {}
- idString :: IsId x => x -> Text
- newtype TeamId = TI {}
- data Team = Team {}
- data TeamMember = TeamMember {}
- data WithDefault a
- data NotifyOption
- data UserNotifyProps = UserNotifyProps {}
- data ChannelNotifyProps = ChannelNotifyProps {}
- emptyUserNotifyProps :: UserNotifyProps
- emptyChannelNotifyProps :: ChannelNotifyProps
- newtype BoolString = BoolString {}
- newtype ChannelId = CI {}
- data Channel = Channel {- channelId :: ChannelId
- channelCreateAt :: UTCTime
- channelUpdateAt :: UTCTime
- channelDeleteAt :: UTCTime
- channelTeamId :: Maybe TeamId
- channelType :: Type
- channelDisplayName :: Text
- channelName :: Text
- channelHeader :: Text
- channelPurpose :: Text
- channelLastPostAt :: UTCTime
- channelTotalMsgCount :: Int
- channelExtraUpdateAt :: UTCTime
- channelCreatorId :: Maybe UserId
 
- newtype SingleChannel = SC Channel
- data ChannelData = ChannelData {}
- data ChannelWithData = ChannelWithData Channel ChannelData
- type Channels = Seq Channel
- data MinChannel = MinChannel {}
- newtype UserId = UI {}
- data InitialLoad = InitialLoad {}
- data User = User {- userId :: UserId
- userCreateAt :: UTCTime
- userUpdateAt :: UTCTime
- userDeleteAt :: UTCTime
- userUsername :: Text
- userAuthData :: Text
- userAuthService :: Text
- userEmail :: Text
- userEmailVerified :: Bool
- userNickname :: Text
- userFirstName :: Text
- userLastName :: Text
- userRoles :: Text
- userNotifyProps :: UserNotifyProps
- userLastPasswordUpdate :: Maybe UTCTime
- userLastPictureUpdate :: Maybe UTCTime
- userLocale :: Text
 
- data PostPropAttachmentField = PostPropAttachmentField {}
- 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 PostProps = PostProps {}
- newtype PostId = PI {}
- newtype FileId = FI {}
- urlForFile :: FileId -> Text
- data PostType
- data Post = Post {- postPendingPostId :: Maybe PostId
- postOriginalId :: Maybe PostId
- postProps :: PostProps
- postRootId :: Maybe PostId
- postFileIds :: Seq FileId
- postId :: PostId
- postType :: PostType
- postMessage :: Text
- postDeleteAt :: Maybe UTCTime
- postHashtags :: Text
- postUpdateAt :: UTCTime
- postUserId :: Maybe UserId
- postCreateAt :: UTCTime
- postParentId :: Maybe PostId
- postChannelId :: ChannelId
- postHasReactions :: Bool
 
- data PendingPost = PendingPost {}
- newtype PendingPostId = PPI {}
- mkPendingPost :: Text -> UserId -> ChannelId -> IO PendingPost
- data FileInfo = FileInfo {- fileInfoId :: FileId
- fileInfoUserId :: UserId
- fileInfoPostId :: Maybe PostId
- fileInfoCreateAt :: UTCTime
- fileInfoUpdateAt :: UTCTime
- fileInfoDeleteAt :: UTCTime
- fileInfoName :: Text
- fileInfoExtension :: Text
- fileInfoSize :: Int
- fileInfoMimeType :: Text
- fileInfoWidth :: Maybe Int
- fileInfoHeight :: Maybe Int
- fileInfoHasPreview :: Bool
 
- data Posts = Posts {}
- millisecondsToUTCTime :: Integer -> UTCTime
- utcTimeToMilliseconds :: UTCTime -> Int
- data MinCommand = MinCommand {}
- data Command = Command {- commandId :: CommandId
- commandToken :: Token
- commandCreateAt :: UTCTime
- commandUpdateAt :: UTCTime
- commandDeleteAt :: UTCTime
- commandCreatorId :: UserId
- commandTeamId :: TeamId
- commandTrigger :: Text
- commandMethod :: Text
- commandUsername :: Text
- commandIconURL :: Text
- commandAutoComplete :: Bool
- commandAutoCompleteDesc :: Text
- commandAutoCompleteHint :: Text
- commandDisplayName :: Text
- commandDescription :: Text
- commandURL :: Text
 
- newtype CommandId = CmdI {}
- data CommandResponseType
- data CommandResponse = CommandResponse {}
- data UsersCreate = UsersCreate {}
- data TeamsCreate = TeamsCreate {}
- data Reaction = Reaction {}
- data PreferenceCategory- = PreferenceCategoryDirectChannelShow
- | PreferenceCategoryGroupChannelShow
- | PreferenceCategoryTutorialStep
- | PreferenceCategoryAdvancedSettings
- | PreferenceCategoryFlaggedPost
- | PreferenceCategoryDisplaySettings
- | PreferenceCategoryTheme
- | PreferenceCategoryAuthorizedOAuthApp
- | PreferenceCategoryNotifications
- | PreferenceCategoryLast
- | PreferenceCategoryOther Text
 
- data PreferenceName = PreferenceName {}
- data PreferenceValue = PreferenceValue {}
- data Preference = Preference {}
- data GroupChannelPreference = GroupChannelPreference {}
- preferenceToGroupChannelPreference :: Preference -> Maybe GroupChannelPreference
- data FlaggedPost = FlaggedPost {}
- preferenceToFlaggedPost :: Preference -> Maybe FlaggedPost
Documentation
runLogger :: ConnectionData -> String -> LogEventType -> IO () Source #
runLoggerS :: Session -> String -> LogEventType -> IO () Source #
mkConnectionData :: Hostname -> Port -> ConnectionContext -> ConnectionData Source #
Creates a structure representing a TLS connection to the server.
mkConnectionDataInsecure :: Hostname -> Port -> ConnectionContext -> ConnectionData Source #
Plaintext HTTP instead of a TLS connection.
initConnectionData :: Hostname -> Port -> IO ConnectionData Source #
withLogger :: ConnectionData -> Logger -> ConnectionData Source #
Constructors
| Team | |
| Fields 
 | |
data WithDefault a Source #
Instances
| Functor WithDefault Source # | |
| Eq a => Eq (WithDefault a) Source # | |
| Ord a => Ord (WithDefault a) Source # | |
| Read a => Read (WithDefault a) Source # | |
| Show a => Show (WithDefault a) Source # | |
| FromJSON t => FromJSON (WithDefault t) Source # | |
data NotifyOption Source #
Constructors
| NotifyOptionAll | |
| NotifyOptionMention | |
| NotifyOptionNone | 
Instances
data UserNotifyProps Source #
Constructors
| UserNotifyProps | |
data ChannelNotifyProps Source #
Constructors
| ChannelNotifyProps | |
Instances
Constructors
| Channel | |
| Fields 
 | |
newtype SingleChannel Source #
data ChannelData Source #
Constructors
| ChannelData | |
data ChannelWithData Source #
Constructors
| ChannelWithData Channel ChannelData | 
Constructors
| User | |
| Fields 
 | |
data PostPropAttachment Source #
Constructors
| PostPropAttachment | |
| Fields 
 | |
Constructors
| PostProps | |
urlForFile :: FileId -> Text Source #
Constructors
| Post | |
| Fields 
 | |
data PendingPost Source #
Constructors
| PendingPost | |
newtype PendingPostId Source #
Instances
mkPendingPost :: Text -> UserId -> ChannelId -> IO PendingPost Source #
Constructors
| FileInfo | |
| Fields 
 | |
Constructors
| Posts | |
| Fields 
 | |
utcTimeToMilliseconds :: UTCTime -> Int Source #
Constructors
| Command | |
| Fields 
 | |
Instances
data CommandResponseType Source #
Constructors
| CommandResponseInChannel | |
| CommandResponseEphemeral | 
data CommandResponse Source #
Constructors
| CommandResponse | |
Constructors
| Reaction | |
| Fields | |
Preferences
data PreferenceCategory Source #
Constructors
data PreferenceName Source #
Constructors
| PreferenceName | |
| Fields | |
data PreferenceValue Source #
Constructors
| PreferenceValue | |
| Fields | |
data GroupChannelPreference Source #
Constructors
| GroupChannelPreference | |
| Fields | |
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