matterhorn-50200.17.0: Terminal client for the Mattermost chat system
Safe HaskellNone
LanguageHaskell2010

Matterhorn.Types

Synopsis

Documentation

data ConnectionStatus Source #

We're either connected or we're not.

Constructors

Connected 
Disconnected 

Instances

Instances details
Eq ConnectionStatus Source # 
Instance details

Defined in Matterhorn.Types

data HelpTopic Source #

Help topics

Instances

Instances details
Eq HelpTopic Source # 
Instance details

Defined in Matterhorn.Types

Show HelpTopic Source # 
Instance details

Defined in Matterhorn.Types

data MHEvent Source #

This represents events that we handle in the main application loop.

Constructors

WSEvent WebsocketEvent

For events that arise from the websocket

WSActionResponse WebsocketActionResponse

For responses to websocket actions

RespEvent (MH ())

For the result values of async IO operations

RefreshWebsocketEvent

Tell our main loop to refresh the websocket connection

WebsocketParseError String

We failed to parse an incoming websocket event

WebsocketDisconnect

The websocket connection went down.

WebsocketConnect

The websocket connection came up.

BGIdle

background worker is idle

BGBusy (Maybe Int)

background worker is busy (with n requests)

RateLimitExceeded Int

A request initially failed due to a rate limit but will be retried if possible. The argument is the number of seconds in which the retry will be attempted.

RateLimitSettingsMissing

A request denied by a rate limit could not be retried because the response contained no rate limit metadata

RequestDropped

A request was reattempted due to a rate limit and was rate limited again

IEvent InternalEvent

MH-internal events

data InternalEvent Source #

Internal application events.

data MHError Source #

Application errors.

Constructors

GenericError Text

A generic error message constructor

NoSuchChannel Text

The specified channel does not exist

NoSuchUser Text

The specified user does not exist

AmbiguousName Text

The specified name matches both a user and a channel

ServerError MattermostError

A Mattermost server error occurred

ClipboardError Text

A problem occurred trying to deal with yanking or the system clipboard

ConfigOptionMissing Text

A missing config option is required to perform an operation

ProgramExecutionFailed Text Text

Args: program name, path to log file. A problem occurred when running the program.

NoSuchScript Text

The specified script was not found

NoSuchHelpTopic Text

The specified help topic was not found

AttachmentException SomeException

IO operations for attaching a file threw an exception

BadAttachmentPath Text

The specified file is either a directory or doesn't exist

AsyncErrEvent SomeException

For errors that arise in the course of async IO operations

Instances

Instances details
Show MHError Source # 
Instance details

Defined in Matterhorn.Types

data CPUUsagePolicy Source #

The policy for CPU usage.

The idea is that Matterhorn can benefit from using multiple CPUs, but the exact number is application-determined. We expose this policy setting to the user in the configuration.

Constructors

SingleCPU

Constrain the application to use one CPU.

MultipleCPUs

Permit the usage of multiple CPUs (the exact number is determined by the application).

Instances

Instances details
Eq CPUUsagePolicy Source # 
Instance details

Defined in Matterhorn.Types

Show CPUUsagePolicy Source # 
Instance details

Defined in Matterhorn.Types

class (Show a, Eq a, Ord a) => SemEq a where Source #

Types that provide a "semantically equal" operation. Two values may be semantically equal even if they are not equal according to Eq if, for example, they are equal on the basis of some fields that are more pertinent than others.

Methods

semeq :: a -> a -> Bool Source #

Instances

Instances details
SemEq Name Source # 
Instance details

Defined in Matterhorn.Types

Methods

semeq :: Name -> Name -> Bool Source #

SemEq a => SemEq (Maybe a) Source # 
Instance details

Defined in Matterhorn.Types

Methods

semeq :: Maybe a -> Maybe a -> Bool Source #

handleEventWith :: [Event -> MH Bool] -> Event -> MH Bool Source #

Given a list of event handlers and an event, try to handle the event with the handlers in the specified order. If a handler returns False (indicating it did not handle the event), try the next handler until either a handler returns True or all handlers are tried. Returns True if any handler handled the event or False otherwise.

data ConnectionInfo Source #

Our ConnectionInfo contains exactly as much information as is necessary to start a connection with a Mattermost server. This is built up during interactive authentication and then is used to log in.

If the access token field is non-empty, that value is used and the username and password values are ignored.

data ViewMessageWindowTab Source #

Handles for the View Message window's tabs.

Constructors

VMTabMessage

The message tab.

VMTabReactions

The reactions tab.

data ThreadOrientation Source #

Constructors

ThreadBelow

Show the thread below the channel message area.

ThreadAbove

Show the thread above the channel message area.

ThreadLeft

Show the thread to the left of the channel message area.

ThreadRight

Show the thread to the right of the channel message area.

data ChannelListOrientation Source #

Constructors

ChannelListLeft

Show the channel list to the left of the message area.

ChannelListRight

Show the channel list to the right of the message area.

data ChannelTopicDialogState Source #

The state of the channel topic editor window.

Constructors

ChannelTopicDialogState 

Fields

data Config Source #

This is how we represent the user's configuration. Most fields correspond to configuration file settings (see Config.hs) but some are for internal book-keeping purposes only.

Constructors

Config 

Fields

Instances

Instances details
Eq Config Source # 
Instance details

Defined in Matterhorn.Types

Methods

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

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

Show Config Source # 
Instance details

Defined in Matterhorn.Types

data PasswordSource Source #

A user password is either given to us directly, or a command which we execute to find the password.

data TokenSource Source #

An access token source.

data MatchType Source #

Instances

Instances details
Eq MatchType Source # 
Instance details

Defined in Matterhorn.Types

Show MatchType Source # 
Instance details

Defined in Matterhorn.Types

data PostListContents Source #

Mode type for the current contents of the post list window

data AuthenticationException Source #

The sum type of exceptions we expect to encounter on authentication failure. We encode them explicitly here so that we can print them in a more user-friendly manner than just show.

data BackgroundInfo Source #

The state of the UI diagnostic indicator for the async worker thread.

Constructors

Disabled

Disable (do not show) the indicator.

Active

Show the indicator when the thread is working.

ActiveCount

Show the indicator when the thread is working, but include the thread's work queue length.

Instances

Instances details
Eq BackgroundInfo Source # 
Instance details

Defined in Matterhorn.Types

Show BackgroundInfo Source # 
Instance details

Defined in Matterhorn.Types

type RequestChan = TChan (IO (Maybe (MH ()))) Source #

A RequestChan is a queue of operations we have to perform in the background to avoid blocking on the main loop

data UserFetch Source #

A user fetching strategy.

Constructors

UserFetchById UserId

Fetch the user with the specified ID.

UserFetchByUsername Text

Fetch the user with the specified username.

UserFetchByNickname Text

Fetch the user with the specified nickname.

Instances

Instances details
Eq UserFetch Source # 
Instance details

Defined in Matterhorn.Types

Show UserFetch Source # 
Instance details

Defined in Matterhorn.Types

data ChannelListGroup Source #

The type of channel list group headings. Integer arguments indicate total number of channels in the group that have unread activity.

data TeamState Source #

All application state specific to a team, along with state specific to our user interface's presentation of that team. We include the UI state relevant to the team so that we can easily switch which team the UI is presenting without having to reinitialize the UI from the new team. This allows the user to be engaged in just about any application activity while viewing a team, switch to another team, and return to the original team and resume what they were doing, all without us doing any work.

Constructors

TeamState 

Fields

data ChatState Source #

This type represents the current state of our application at any given time.

Instances

Instances details
MonadState ChatState MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

get :: MH ChatState #

put :: ChatState -> MH () #

state :: (ChatState -> (a, ChatState)) -> MH a #

withCurrentTeam :: (TeamId -> MH ()) -> MH () Source #

whenMode :: TeamId -> Mode -> MH () -> MH () Source #

data GlobalEditState Source #

The GlobalEditState value contains state not specific to any single editor.

Constructors

GlobalEditState 

Fields

data PostListWindowState Source #

The state of the post list window.

data UserSearchScope Source #

The scope for searching for users in a user list window.

data ChannelSearchScope Source #

The scope for searching for channels to join.

Constructors

AllChannels 

data ListWindowState a b Source #

The state of the search result list window. Type a is the type of data in the list. Type b is the search scope type.

Constructors

ListWindowState 

Fields

listWindowFetchResults :: forall a b. Lens' (ListWindowState a b) (b -> Session -> Text -> IO (Vector a)) Source #

data ChatResources Source #

ChatResources represents configuration and connection-related information, as opposed to current model or view information. Information that goes in the ChatResources value should be limited to information that we read or set up prior to setting up the bulk of the application state.

data Cmd Source #

A Cmd packages up a CmdArgs specifier and the CmdExec implementation with a name and a description.

Constructors

forall a. Cmd 

Fields

commandName :: Cmd -> Text Source #

Helper function to extract the name out of a Cmd value

data CmdArgs :: Type -> Type where Source #

The CmdArgs type represents the arguments to a slash-command; the type parameter represents the argument structure.

Constructors

NoArg :: CmdArgs () 
LineArg :: Text -> CmdArgs Text 
UserArg :: CmdArgs rest -> CmdArgs (Text, rest) 
ChannelArg :: CmdArgs rest -> CmdArgs (Text, rest) 
TokenArg :: Text -> CmdArgs rest -> CmdArgs (Text, rest) 

data MH a Source #

A value of type MH a represents a computation that can manipulate the application state and also request that the application quit

Instances

Instances details
Monad MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

(>>=) :: MH a -> (a -> MH b) -> MH b #

(>>) :: MH a -> MH b -> MH b #

return :: a -> MH a #

Functor MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

fmap :: (a -> b) -> MH a -> MH b #

(<$) :: a -> MH b -> MH a #

MonadFail MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

fail :: String -> MH a #

Applicative MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

pure :: a -> MH a #

(<*>) :: MH (a -> b) -> MH a -> MH b #

liftA2 :: (a -> b -> c) -> MH a -> MH b -> MH c #

(*>) :: MH a -> MH b -> MH b #

(<*) :: MH a -> MH b -> MH a #

MonadIO MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

liftIO :: IO a -> MH a #

MonadState ChatState MH Source # 
Instance details

Defined in Matterhorn.Types

Methods

get :: MH ChatState #

put :: ChatState -> MH () #

state :: (ChatState -> (a, ChatState)) -> MH a #

runMHEvent :: ChatState -> MH () -> EventM Name (Next ChatState) Source #

Run an MM computation, choosing whether to continue or halt based on the resulting

mh :: EventM Name a -> MH a Source #

lift a computation in EventM into MH

mhHandleEventLensed :: Lens' ChatState b -> (e -> b -> EventM Name b) -> e -> MH () Source #

gets :: MonadState s m => (s -> a) -> m a #

Gets specific component of the state, using a projection function supplied.

mhError :: MHError -> MH () Source #

Log and raise an error.

mhLog :: LogCategory -> Text -> MH () Source #

Log a message.

mhGetIOLogger :: MH (LogCategory -> Text -> IO ()) Source #

Get a logger suitable for use in IO. The logger always logs using the MH monad log context at the time of the call to mhGetIOLogger.

data LogContext Source #

Logging context information, in the event that metadata should accompany a log message.

Instances

Instances details
Eq LogContext Source # 
Instance details

Defined in Matterhorn.Types

Show LogContext Source # 
Instance details

Defined in Matterhorn.Types

withLogContext :: (Maybe LogContext -> Maybe LogContext) -> MH a -> MH a Source #

Use a modified logging context for the duration of the specified MH action.

getLogContext :: MH (Maybe LogContext) Source #

Get the current logging context.

data LogMessage Source #

A log message.

Constructors

LogMessage 

Fields

Instances

Instances details
Eq LogMessage Source # 
Instance details

Defined in Matterhorn.Types

Show LogMessage Source # 
Instance details

Defined in Matterhorn.Types

data LogCommand Source #

A logging thread command.

Constructors

LogToFile FilePath

Start logging to the specified path.

LogAMessage !LogMessage

Log the specified message.

StopLogging

Stop any active logging.

ShutdownLogging

Shut down.

GetLogDestination

Ask the logging thread about its active logging destination.

LogSnapshot FilePath

Ask the logging thread to dump the current buffer to the specified destination.

Instances

Instances details
Show LogCommand Source # 
Instance details

Defined in Matterhorn.Types

data LogCategory Source #

Log message tags.

Instances

Instances details
Eq LogCategory Source # 
Instance details

Defined in Matterhorn.Types

Show LogCategory Source # 
Instance details

Defined in Matterhorn.Types

data LogManager Source #

A handle to the log manager thread.

requestQuit :: MH () Source #

This will request that after this computation finishes the application should exit

data HighlightSet Source #

The set of usernames, channel names, and language names used for highlighting when rendering messages.

moveLeft :: Eq a => a -> [a] -> [a] Source #

moveRight :: Eq a => a -> [a] -> [a] Source #