terminal-0.1.0.0: Portable terminal interaction library

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Terminal

Contents

Synopsis

Getting started

TerminalT

data TerminalT m a Source #

Instances
MonadTrans TerminalT Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

lift :: Monad m => m a -> TerminalT m a #

Eq (Annotation (TerminalT m)) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Monad m => Monad (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

(>>=) :: TerminalT m a -> (a -> TerminalT m b) -> TerminalT m b #

(>>) :: TerminalT m a -> TerminalT m b -> TerminalT m b #

return :: a -> TerminalT m a #

fail :: String -> TerminalT m a #

Functor m => Functor (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

fmap :: (a -> b) -> TerminalT m a -> TerminalT m b #

(<$) :: a -> TerminalT m b -> TerminalT m a #

Ord (Annotation (TerminalT m)) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Show (Annotation (TerminalT m)) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Applicative m => Applicative (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

pure :: a -> TerminalT m a #

(<*>) :: TerminalT m (a -> b) -> TerminalT m a -> TerminalT m b #

liftA2 :: (a -> b -> c) -> TerminalT m a -> TerminalT m b -> TerminalT m c #

(*>) :: TerminalT m a -> TerminalT m b -> TerminalT m b #

(<*) :: TerminalT m a -> TerminalT m b -> TerminalT m a #

MonadIO m => MonadIO (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

liftIO :: IO a -> TerminalT m a #

MonadThrow m => MonadThrow (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

throwM :: Exception e => e -> TerminalT m a #

MonadCatch m => MonadCatch (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

catch :: Exception e => TerminalT m a -> (e -> TerminalT m a) -> TerminalT m a #

MonadMask m => MonadMask (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

mask :: ((forall a. TerminalT m a -> TerminalT m a) -> TerminalT m b) -> TerminalT m b #

uninterruptibleMask :: ((forall a. TerminalT m a -> TerminalT m a) -> TerminalT m b) -> TerminalT m b #

generalBracket :: TerminalT m a -> (a -> ExitCase b -> TerminalT m c) -> (a -> TerminalT m b) -> TerminalT m (b, c) #

MonadIO m => MonadInput (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

waitMapInterruptAndEvents :: (STM () -> STM Event -> STM a) -> TerminalT m a Source #

(MonadIO m, MonadThrow m) => MonadColorPrinter (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

(MonadIO m, MonadThrow m) => MonadFormatPrinter (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

(MonadIO m, MonadThrow m) => MonadPrettyPrinter (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Associated Types

data Annotation (TerminalT m) :: Type Source #

(MonadIO m, MonadThrow m) => MonadPrinter (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

(MonadIO m, MonadThrow m) => MonadTerminal (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

data Annotation (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Printing & Screen Modification

MonadPrinter

class Monad m => MonadPrinter m where Source #

This class describes an environment that Unicode text can be printed to. This might either be file or a terminal.

  • Instances shall implement the concept of lines and line width.
  • Instances shall implement the concept of a carriage that can be set to the beginning of the next line.
  • It is assumed that the carriage automatically moves to the beginning of the next line if the end of the current line is reached.
  • Instances shall be Unicode aware or must at least be able to print a replacement character.
  • Implementations must be aware of infinite lazy Strings and long Texts. Strings should be printed character wise as evaluating them might trigger exceptions at any point. Long text should be printed chunk wise in order to stay interruptible.
  • Implementations must not use an unbounded output buffer. Print operations shall block and be interruptible when the output buffer is full.
  • Instances shall not interpret any control characters but \n (new line, as generated by putLn, and \t (horizontal tabulator).
  • Especially escape sequences shall be filtered or at least defused by removing the leading \ESC. Text formatting shall be done with the designated classes like MonadPrettyPrinter, MonadFormatPrinter and MonadColorPrinter. Allowing control sequences would cause a dependency on certain terminal types, but might also be an underrated security risk as modern terminals are highly programmable and should not be fed with untrusted input.

Minimal complete definition

putChar, getLineWidth

Methods

putLn :: m () Source #

Move the carriage to the beginning of the next line.

putChar :: Char -> m () Source #

Print a single printable character or one of the allowed control characters.

putString :: String -> m () Source #

Print a String.

putStringLn :: String -> m () Source #

Print a String and an additional newline.

putText :: Text -> m () Source #

Print a Text.

putTextLn :: Text -> m () Source #

Print a Text and an additional newline.

flush :: m () Source #

Flush the output buffer and make the all previous output actually visible after a reasonably short amount of time.

  • The operation may return before the buffer has actually been flushed.

getLineWidth :: m Int Source #

Get the current line width.

  • The operation may return the last known line width and may not be completely precise when I/O is asynchronous.
  • This operations shall not block too long and rather be called more often in order to adapt to changes in line width.

MonadPrettyPrinter

class MonadPrinter m => MonadPrettyPrinter m where Source #

This class is the foundation for all environments that allow annotated text and Documents to be printed to.

  • Prefer using the Doc module and the putDoc operation whenever trying to print structured or formatted text as it automatically deals with nested annotations and the current line width.

Associated Types

data Annotation m Source #

This associated type represents all possible annotations that are available in the current environment.

When writing polymorphic code against these monadic interfaces the concrete instantiation of this type is usually unknown and class instances are generally advised to not expose value constructors for this type.

Instead, subclasses like MonadFormatPrinter and MonadColorPrinter offer abstract value constructors like bold, underlined, inverted which are then given meaning by the concrete class instance. The environment AnsiTerminalT for example implements all of these classes.

Methods

putDoc :: Doc (Annotation m) -> m () Source #

Print an annotated Doc.

  • This operation performs resetAnnotations on entry and on exit.
  • This operation can deal with nested annotations (see example).

Example:

{--}
import Control.Monad.Terminal
import Data.Text.Prettyprint.Doc

printer :: (MonadFormatPrinter m, MonadColorPrinter m) => m ()
printer = putDoc $ annotate (foreground $ bright Blue) "This is blue!" <> line
                <> annotate bold ("Just bold!" <> otherDoc <> "..just bold again")

otherDoc :: (MonadColorPrinter m, Annotation m ~ ann) => Doc ann
otherDoc = annotate (background $ dull Red) " BOLD ON RED BACKGROUND "

Note the necessary unification of Annotation m and ann in the definition of otherDoc!

putDocLn :: Doc (Annotation m) -> m () Source #

Like putDoc but adds an additional newline.

setAnnotation :: Annotation m -> m () Source #

Set an annotation so that it affects subsequent output.

resetAnnotation :: Annotation m -> m () Source #

Reset an annotation so that it does no longer affect subsequent output.

  • Binary attributes like bold or underlined shall just be reset to their opposite.
  • For non-binary attributes like colors all of their possible values shall be treated as equal, so that
  setAnnotation (foreground $ bright Blue) >> resetAnnotation (foreground $ dull Red)
  

results in the foreground color attribute reset afterwards whereas after

  setAnnotation (foreground $ bright Blue) >> resetAnnotation (background $ dull Red)
  

the foreground color is still set as bright Blue.

resetAnnotations :: m () Source #

Reset all annotations to their default.

pprint :: (MonadPrettyPrinter m, Pretty a) => a -> m () Source #

MonadFormatPrinter

class MonadPrettyPrinter m => MonadFormatPrinter m where Source #

This class offers abstract constructors for text formatting annotations.

Methods

bold :: Annotation m Source #

This annotation makes text appear bold.

italic :: Annotation m Source #

This annotation makes text appear italic.

underlined :: Annotation m Source #

This annotation makes text appear underlined.

MonadColorPrinter

class MonadPrettyPrinter m => MonadColorPrinter m where Source #

This class offers abstract value constructors for foreground and background coloring.

Methods

inverted :: Annotation m Source #

This annotation swaps foreground and background color.

  • This operation is idempotent: Applying the annotation a second time won't swap it back. Use resetAnnotation instead.

foreground :: Color -> Annotation m Source #

This annotation sets the foreground color (the text color).

background :: Color -> Annotation m Source #

This annotation sets the background color.

data Color Source #

Constructors

Color ColorMode BasicColor 
Instances
Eq Color Source # 
Instance details

Defined in Control.Monad.Terminal.Printer

Methods

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

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

Ord Color Source # 
Instance details

Defined in Control.Monad.Terminal.Printer

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

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

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Show Color Source # 
Instance details

Defined in Control.Monad.Terminal.Printer

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

MonadTerminal

class (MonadInput m, MonadPrettyPrinter m, MonadFormatPrinter m, MonadColorPrinter m) => MonadTerminal m where Source #

Methods

moveCursorUp :: Int -> m () Source #

Move the cursor n lines up. Do not change column.

moveCursorDown :: Int -> m () Source #

Move the cursor n lines down. Do not change column.

moveCursorLeft :: Int -> m () Source #

Move the cursor n columns to the left. Do not change line.

moveCursorRight :: Int -> m () Source #

Move the cursor n columns to the right. Do not change line.

getCursorPosition :: m (Int, Int) Source #

Get the current cursor position. `(0,0) is the upper left of the screen.

setCursorPosition :: (Int, Int) -> m () Source #

Set the cursor position. `(0,0)` is the upper left of the screen.

setCursorPositionVertical :: Int -> m () Source #

Set the vertical cursor position to the nth line. Do not change column.

setCursorPositionHorizontal :: Int -> m () Source #

Set the horizontal cursor position to the nth column. Do not change line.

saveCursorPosition :: m () Source #

Save the current cursor position to be restored later by restoreCursorPosition.

restoreCursorPosition :: m () Source #

Restore cursor to position previously saved by saveCursorPosition.

showCursor :: m () Source #

Show the cursor.

hideCursor :: m () Source #

Hide the cursor.

clearLine :: m () Source #

Clear the entire line containing the cursor.

clearLineLeft :: m () Source #

Clear the line from cursor left.

clearLineRight :: m () Source #

Clear the line from cursor right.

clearScreen :: m () Source #

Clear the entire screen.

clearScreenAbove :: m () Source #

Clear the screen above the cursor.

clearScreenBelow :: m () Source #

Clear the screen below the cursor.

getScreenSize :: m (Int, Int) Source #

useAlternateScreenBuffer :: Bool -> m () Source #

Whether or not to use the alternate screen buffer.

  • The main screen buffer content is preserved and restored when leaving the alternate screen screen buffer.
  • The dimensions of the alternate screen buffer are exactly those of the screen.

Event Processing

MonadInput

class MonadIO m => MonadInput m where Source #

This monad describes an environment that maintains a stream of Events and offers out-of-band signaling for interrupts.

  • An interrupt shall occur if the user either presses CTRL+C or any other mechanism the environment designates for that purpose.
  • Implementations shall maintain an interrupt flag that is set when an interrupt occurs. Computations in this monad shall check and reset this flag regularly. If the execution environment finds this flag still set when trying to signal another interrupt, it shall throw UserInterrupt to the seemingly unresponsive computation.
  • When an interrupt is signaled through the flag, an InterruptEvent must be added to the event stream in the same transaction. This allows to flush all unprocessed events from the stream that occured before the interrupt.

Methods

waitMapInterruptAndEvents :: (STM () -> STM Event -> STM a) -> m a Source #

Wait for the next interrupt or the next event transformed by a given mapper.

  • The first mapper parameter is a transaction that succeeds as soon as the interrupt flag gets set. Executing this transaction resets the interrupt flag. If the interrupt flag is not reset before a second interrupt occurs, the current thread shall receive an UserInterrupt.
  • The second mapper parameter is a transaction that succeeds as as soon as the next event arrives and removes that event from the stream of events. It may be executed several times within the same transaction, but might not succeed every time.
Instances
MonadIO m => MonadInput (TerminalT m) Source # 
Instance details

Defined in Control.Monad.Terminal.TerminalT

Methods

waitMapInterruptAndEvents :: (STM () -> STM Event -> STM a) -> TerminalT m a Source #

waitEvent

waitEvent :: MonadInput m => m Event Source #

Wait for the next event.

  • Returns as soon as an event occurs.
  • This operation resets the interrupt flag it returns, signaling responsiveness to the execution environment.
  • InterruptEvents occur in the event stream at their correct position wrt to ordering of events. They are returned as regular events. This is eventually not desired when trying to handle interrupts with highest priority and waitInterruptOrElse should be considered then.

waitEventOrElse

waitEventOrElse :: MonadInput m => STM a -> m (Either Event a) Source #

Wait simultaneously for the next event or a given transaction.

  • Returns as soon as either an event occurs or the given transaction succeeds.
  • This operation resets the interrupt flag whenever it returns, signaling responsiveness to the execution environment.
  • InterruptEvents occur in the event stream at their correct position wrt to ordering of events. They are returned as regular events. This is eventually not desired when trying to handle interrupts with highest priority and waitInterruptOrElse should be considered then.

waitInterruptOrElse

waitInterruptOrElse :: MonadInput m => STM a -> m (Maybe a) Source #

Wait simultaneously for the next interrupt or a given transaction.

  • Returns Nothing on interrupt and Just when the supplied transaction succeeds first.
  • This operation resets the interrupt flag, signaling responsiveness to the execution environment.
  • All pending events up to and including the InterruptEvent are flushed from the event stream in case of an interrupt.

Events

Keys & Modifiers

data Key Source #

Instances
Eq Key Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Methods

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

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

Ord Key Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

data Modifiers Source #

Instances
Eq Modifiers Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Ord Modifiers Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Show Modifiers Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Semigroup Modifiers Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Monoid Modifiers Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Bits Modifiers Source # 
Instance details

Defined in Control.Monad.Terminal.Input

Mouse Events

Window Events

Device Events

Low-Level

Terminal

data Terminal Source #

Constructors

Terminal 

Fields

  • termType :: ByteString

    The terminal identification string usually extracted from the environment variable TERM. Should contain values like xterm or `rxvt-unicode`.

  • termInput :: STM Event

    A stream of input events. The transaction will succeed as soon as the next input event becomes available.

    Note: Trying to read more than one event within the same transaction might be successfull, but might also lead to undesired behaviour as the transaction will block until all of its preconditions are fulfilled. Some form of orElse needs to be used in a correct way for reading several events at once.

  • termOutput :: Text -> STM ()

    This transaction appends a piece of Text to the output buffer. It shall block when the buffer exeeded its capacity and unblock as soon as space becomes available again.

    Note: All implementations must limit the size of the output buffer or the application is at risk of running out of memory when writing much faster than the terminal can read. Using a TMVar as a buffer of size 1 is perfectly fine here.

  • termInterrupt :: STM ()

    This transaction succeeds as soon as an interrupt event occurs. Executing the transaction shall reset an interrupt flag maintained by a supervising background thread.

    It is mandatory to regularly check this transaction in order to signal responsiveness to the background thread. The supervisor is otherwise advised to terminate the program as soon as a second interrupt arrives.

    Note: This is a very low-level operation. Operations like waitEvent, waitEventOrElse or waitInterruptOrElse are more convenient and do this automatically.

  • termFlush :: STM ()

    This operations flushes the output buffer. Whether it blocks or not until the buffer has actually been flushed shall be undefined (there might be other buffers involved that cannot be force-flushed so it is probably better to not give any guarantees here).

  • termScreenSize :: STM (Int, Int)

    This transaction shall return the latest known screen size without blocking. The first parameter denotes the number of rows and the one the number of columns.

  • termSpecialChars :: Char -> Maybe Event
     

Decoding

newtype Decoder Source #

The type Decoder represents a finite state transducer.

Values of this type can only be constructed by tying the knot which causes the resulting transducer to have one entry point but no exits. Intermediate state can be passed as closures. See below for an example.

Constructors

Decoder 

Fields