terminal-0.2.0.0: Portable terminal interaction library

Safe HaskellNone
LanguageHaskell2010

System.Terminal

Contents

Synopsis

Getting started

withTerminal

withTerminal :: (MonadIO m, MonadMask m) => (LocalTerminal -> m a) -> m a Source #

Run the given handler with the locally connected terminal (stdin / stdout).

import System.Terminal

main :: IO ()
main = withTerminal $ runTerminalT do
    putTextLn "Hello there, please press a button!"
    flush
    ev <- waitEvent
    putStringLn $ "Event was " ++ show ev
    flush

TerminalT

runTerminalT :: (MonadIO m, MonadMask m, Terminal t) => TerminalT t m a -> t -> m a Source #

Run a TerminalT application on the given terminal.

data TerminalT t m a Source #

This monad transformer represents terminal applications.

It implements all classes in this module and should serve as a good foundation for most use cases.

Note that it is not necessary nor recommended to have this type in every signature. Keep your application abstract and mention TerminalT only once at the top level.

Example:

main :: IO ()
main = withTerminal (runTerminalT myApplication)

myApplication :: (MonadPrinter m) => m ()
myApplication = do
    putTextLn "Hello world!"
    flush
Instances
Eq (Color (TerminalT t m)) Source # 
Instance details

Defined in System.Terminal.TerminalT

Methods

(==) :: Color (TerminalT t m) -> Color (TerminalT t m) -> Bool #

(/=) :: Color (TerminalT t m) -> Color (TerminalT t m) -> Bool #

Eq (Attribute (TerminalT t m)) Source # 
Instance details

Defined in System.Terminal.TerminalT

Methods

(==) :: Attribute (TerminalT t m) -> Attribute (TerminalT t m) -> Bool #

(/=) :: Attribute (TerminalT t m) -> Attribute (TerminalT t m) -> Bool #

Ord (Color (TerminalT t m)) Source # 
Instance details

Defined in System.Terminal.TerminalT

Methods

compare :: Color (TerminalT t m) -> Color (TerminalT t m) -> Ordering #

(<) :: Color (TerminalT t m) -> Color (TerminalT t m) -> Bool #

(<=) :: Color (TerminalT t m) -> Color (TerminalT t m) -> Bool #

(>) :: Color (TerminalT t m) -> Color (TerminalT t m) -> Bool #

(>=) :: Color (TerminalT t m) -> Color (TerminalT t m) -> Bool #

max :: Color (TerminalT t m) -> Color (TerminalT t m) -> Color (TerminalT t m) #

min :: Color (TerminalT t m) -> Color (TerminalT t m) -> Color (TerminalT t m) #

Ord (Attribute (TerminalT t m)) Source # 
Instance details

Defined in System.Terminal.TerminalT

Show (Color (TerminalT t m)) Source # 
Instance details

Defined in System.Terminal.TerminalT

Methods

showsPrec :: Int -> Color (TerminalT t m) -> ShowS #

show :: Color (TerminalT t m) -> String #

showList :: [Color (TerminalT t m)] -> ShowS #

Show (Attribute (TerminalT t m)) Source # 
Instance details

Defined in System.Terminal.TerminalT

MonadTrans (TerminalT t) Source # 
Instance details

Defined in System.Terminal.TerminalT

Methods

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

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

Defined in System.Terminal.TerminalT

Methods

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

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

return :: a -> TerminalT t m a #

fail :: String -> TerminalT t m a #

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

Defined in System.Terminal.TerminalT

Methods

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

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

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

Defined in System.Terminal.TerminalT

Methods

pure :: a -> TerminalT t m a #

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

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

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

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

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

Defined in System.Terminal.TerminalT

Methods

liftIO :: IO a -> TerminalT t m a #

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

Defined in System.Terminal.TerminalT

Methods

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

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

Defined in System.Terminal.TerminalT

Methods

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

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

Defined in System.Terminal.TerminalT

Methods

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

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

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

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

Defined in System.Terminal.TerminalT

Associated Types

data Color (TerminalT t m) :: Type Source #

(MonadIO m, MonadThrow m, Terminal t) => MonadFormattingPrinter (TerminalT t m) Source # 
Instance details

Defined in System.Terminal.TerminalT

(MonadIO m, MonadThrow m, Terminal t) => MonadMarkupPrinter (TerminalT t m) Source # 
Instance details

Defined in System.Terminal.TerminalT

Associated Types

data Attribute (TerminalT t m) :: Type Source #

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

Defined in System.Terminal.TerminalT

(MonadIO m, MonadThrow m, Terminal t) => MonadScreen (TerminalT t m) Source # 
Instance details

Defined in System.Terminal.TerminalT

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

Defined in System.Terminal.TerminalT

Methods

awaitWith :: (STM Interrupt -> STM Event -> STM a) -> TerminalT t m a Source #

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

Defined in System.Terminal.TerminalT

data Color (TerminalT t m) Source # 
Instance details

Defined in System.Terminal.TerminalT

data Attribute (TerminalT t m) Source # 
Instance details

Defined in System.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 pass control characters in text to the printer (not even line break). Control characters shall be replaced with �. Text formatting shall be done with the designated classes extending MonadMarkupPrinter. Allowing control sequences would cause a dependency on certain terminal types, but also pose an underrated security risk as modern terminals are highly programmable and should not be fed with untrusted input.

Minimal complete definition

putLn, putChar, putText, getLineWidth

Methods

putLn :: m () Source #

Move the carriage to the beginning of the next line.

putChar :: Char -> m () Source #

Print a single character.

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.

MonadMarkupPrinter

class MonadPrinter m => MonadMarkupPrinter m where Source #

This class introduces abstract constructors for text markup.

Minimal complete definition

resetAttribute, resetAttributes, resetsAttribute

Associated Types

data Attribute m Source #

This associated type represents all possible attributes 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 MonadFormattingPrinter and MonadColorPrinter offer abstract value constructors like bold, underlined, inverted which are then given meaning by the concrete class instance.

Methods

setAttribute :: Attribute m -> m () Source #

resetAttribute :: Attribute m -> m () Source #

Reset an attribute 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
  setAttribute (foreground $ bright blue) >> resetAttribute (foreground red)
  

results in the foreground color attribute reset afterwards whereas after

  setAttribute (foreground $ bright blue) >> resetAttribute (background red)
  

the foreground color is still set as bright blue.

resetAttributes :: m () Source #

Reset all attributes to their default.

resetsAttribute :: Attribute m -> Attribute m -> Bool Source #

Shall determine wheter two attribute values would override each other or can be applied independently.

  • Shall obey the laws of equivalence.

MonadFormattingPrinter

class MonadMarkupPrinter m => MonadFormattingPrinter m where Source #

Methods

bold :: Attribute m Source #

This attribute makes text appear bold.

italic :: Attribute m Source #

This attribute makes text appear italic.

underlined :: Attribute m Source #

This attribute makes text appear underlined.

inverted :: Attribute m Source #

This attribute swaps foreground and background (color).

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

MonadColorPrinter

class MonadMarkupPrinter m => MonadColorPrinter m where Source #

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

Associated Types

data Color m Source #

Methods

black :: Color m Source #

red :: Color m Source #

green :: Color m Source #

yellow :: Color m Source #

blue :: Color m Source #

magenta :: Color m Source #

cyan :: Color m Source #

white :: Color m Source #

bright :: Color m -> Color m Source #

foreground :: Color m -> Attribute m Source #

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

background :: Color m -> Attribute m Source #

This attribute sets the background color.

Pretty Printing

putDoc :: MonadMarkupPrinter m => Doc (Attribute m) -> m () Source #

Print an annotated Doc.

Example:

import System.Terminal
import Data.Text.Prettyprint.Doc

printer :: (MonadFormatingPrinter 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, Attribute m ~ ann) => Doc ann
otherDoc = annotate (background red) " BOLD ON RED BACKGROUND "

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

putDocLn :: MonadMarkupPrinter m => Doc (Attribute m) -> m () Source #

Like putDoc but adds an additional newline.

putPretty :: (MonadMarkupPrinter m, Pretty a) => a -> m () Source #

Prints types instantiating the Pretty class.

putPrettyLn :: (MonadMarkupPrinter m, Pretty a) => a -> m () Source #

Prints types instantiating the Pretty class and adds an additional newline.

putSimpleDocStream :: MonadMarkupPrinter m => SimpleDocStream (Attribute m) -> m () Source #

Prints SimpleDocStreams (rather internal and not for the average user).

MonadScreen

class MonadPrinter m => MonadScreen m where Source #

Methods

getWindowSize :: m Size Source #

Get the dimensions of the visible window.

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.

moveCursorForward :: Int -> m () Source #

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

moveCursorBackward :: Int -> m () Source #

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

getCursorPosition :: m Position Source #

Get the current cursor position as reported by the terminal.

  • Position 0 0 is the upper left of the window.
  • The cursor is always within window bounds.
  • This operation causes a round-trip to the terminal and shall be used sparely (e.g. on window size change).

setCursorPosition :: Position -> m () Source #

Set the cursor position.

  • Position 0 0 is the upper left of the window.
  • The resulting cursor position is undefined when it is outside the window bounds.

setCursorRow :: Int -> m () Source #

Set the cursor row.

  • 0 is the topmost row.

setCursorColumn :: Int -> m () Source #

Set the cursor column.

  • 0 is the leftmost column.

saveCursor :: m () Source #

Save cursor position and attributes.

restoreCursor :: m () Source #

Restore cursor position and attributes.

  • Restores the cursor as previously saved by saveCursor.
  • The cursor position is strictly relative to the visible window and does not take eventual scrolling into account. The advantage of this operation is that it does not require transmission of coordinates and attributes to the terminal and is therefor slightly more efficient than all other alternatives.
  • Only use this when auto-wrap is disabled, alternate screen buffer is enabled or you can otherwise guarantee that the window does not scroll between saveCursor and restoreCursor!

insertChars :: Int -> m () Source #

Insert whitespace at the cursor position and shift existing characters to the right.

deleteChars :: Int -> m () Source #

Delete characters and shift existing characters from the right.

eraseChars :: Int -> m () Source #

Replace characters with whitespace.

insertLines :: Int -> m () Source #

Insert lines and shift existing lines downwards.

deleteLines :: Int -> m () Source #

Delete lines and shift up existing lines from below.

eraseInLine :: EraseMode -> m () Source #

Clears characters in the current line.

eraseInDisplay :: EraseMode -> m () Source #

Clears lines above/below the current line.

showCursor :: m () Source #

Show the cursor.

hideCursor :: m () Source #

Hide the cursor.

setAutoWrap :: Bool -> m () Source #

Whether or not to automatically wrap on line ends.

setAlternateScreenBuffer :: 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.

data Size Source #

Constructors

Size 

Fields

Instances
Eq Size Source # 
Instance details

Defined in System.Terminal.MonadScreen

Methods

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

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

Ord Size Source # 
Instance details

Defined in System.Terminal.MonadScreen

Methods

compare :: Size -> Size -> Ordering #

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

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

(>) :: Size -> Size -> Bool #

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

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Show Size Source # 
Instance details

Defined in System.Terminal.MonadScreen

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

data Position Source #

Constructors

Position 

Fields

data EraseMode Source #

Constructors

EraseBackward

Erase left of/above current cursor position.

EraseForward

Erase right of/below current cursor position.

EraseAll

Erase whole line/screen.

MonadTerminal

class (MonadInput m, MonadFormattingPrinter m, MonadColorPrinter m, MonadScreen m) => MonadTerminal m Source #

This is a convenience class combining all other terminal related classes.

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

Defined in System.Terminal.TerminalT

Event Processing

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.

Methods

awaitWith :: (STM Interrupt -> STM Event -> STM a) -> m a Source #

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

  • The first mapper parameter is a transaction that succeeds as soon as an interrupt occurs. Executing this transaction resets the interrupt flag. When a second interrupt occurs before the interrupt flag has been reset, 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 shall be executed at most once within a single transaction or the transaction would block until the requested number of events is available.
  • The mapper may also be used in order to additionally wait on external events (like an Async to complete).
Instances
(MonadIO m, Terminal t) => MonadInput (TerminalT t m) Source # 
Instance details

Defined in System.Terminal.TerminalT

Methods

awaitWith :: (STM Interrupt -> STM Event -> STM a) -> TerminalT t m a Source #

awaitEvent

awaitEvent :: MonadInput m => m (Either Interrupt Event) Source #

Wait for the next event.

  • Returns as soon as an interrupt or a regular event occurs.
  • This operation resets the interrupt flag, signaling responsiveness to the execution environment.

checkInterrupt

checkInterrupt :: MonadInput m => m Bool Source #

Check whether an interrupt is pending.

  • This operation resets the interrupt flag, signaling responsiveness to the execution environment.

Events

data Event Source #

Events emitted by the terminal.

  • Event decoding might be ambique. In case of ambiqueness all possible meaning shall be emitted. The user is advised to only match on events expected in a certain context and ignore all others.
  • Key events are highly ambique: I.e. when the user presses space it might either be meant as a regular text element (like a,b,c) or the focus is on the key itself (like in "Press space to continue...").
  • The story is even more complicated: Depending on terminal type and termios settings, certain control codes have special meaning or not (Ctrl+C sometimes means interrupt, but not if the environment supports delivering it as a signal). Don't wait for Ctrl+C when you mean Interrupt! Example: The tab key will likely emit KeyEvent (CharKey I) ctrlKey and KeyEvent TabKey mempty in most settings.
Instances
Eq Event Source # 
Instance details

Defined in System.Terminal.MonadInput

Methods

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

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

Ord Event Source # 
Instance details

Defined in System.Terminal.MonadInput

Methods

compare :: Event -> Event -> Ordering #

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

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

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Show Event Source # 
Instance details

Defined in System.Terminal.MonadInput

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

data Interrupt Source #

Interrupt is a special type of event that needs to be treated with priority. It is therefor not included in the regular event stream.

Constructors

Interrupt 

Keys & Modifiers

data Key Source #

Events triggered by key press.

Instances
Eq Key Source # 
Instance details

Defined in System.Terminal.MonadInput

Methods

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

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

Ord Key Source # 
Instance details

Defined in System.Terminal.MonadInput

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 System.Terminal.MonadInput

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

data Modifiers Source #

Modifier keys.

Instances
Eq Modifiers Source # 
Instance details

Defined in System.Terminal.MonadInput

Ord Modifiers Source # 
Instance details

Defined in System.Terminal.MonadInput

Show Modifiers Source # 
Instance details

Defined in System.Terminal.MonadInput

Semigroup Modifiers Source # 
Instance details

Defined in System.Terminal.MonadInput

Monoid Modifiers Source # 
Instance details

Defined in System.Terminal.MonadInput

Bits Modifiers Source # 
Instance details

Defined in System.Terminal.MonadInput

Mouse Events

Window Events

Device Events