| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Terminal
Contents
Synopsis
- data TerminalT m a
- runTerminalT :: (MonadIO m, MonadMask m) => TerminalT m a -> Terminal -> m a
- class Monad m => MonadPrinter m where
- class MonadPrinter m => MonadPrettyPrinter m where
- data Annotation m
- putDoc :: Doc (Annotation m) -> m ()
- putDocLn :: Doc (Annotation m) -> m ()
- setAnnotation :: Annotation m -> m ()
- resetAnnotation :: Annotation m -> m ()
- resetAnnotations :: m ()
- pprint :: (MonadPrettyPrinter m, Pretty a) => a -> m ()
- class MonadPrettyPrinter m => MonadFormatPrinter m where
- bold :: Annotation m
- italic :: Annotation m
- underlined :: Annotation m
- class MonadPrettyPrinter m => MonadColorPrinter m where
- inverted :: Annotation m
- foreground :: Color -> Annotation m
- background :: Color -> Annotation m
- dull :: BasicColor -> Color
- bright :: BasicColor -> Color
- data BasicColor
- data Color = Color ColorMode BasicColor
- data ColorMode
- class (MonadInput m, MonadPrettyPrinter m, MonadFormatPrinter m, MonadColorPrinter m) => MonadTerminal m where
- moveCursorUp :: Int -> m ()
- moveCursorDown :: Int -> m ()
- moveCursorLeft :: Int -> m ()
- moveCursorRight :: Int -> m ()
- getCursorPosition :: m (Int, Int)
- setCursorPosition :: (Int, Int) -> m ()
- setCursorPositionVertical :: Int -> m ()
- setCursorPositionHorizontal :: Int -> m ()
- saveCursorPosition :: m ()
- restoreCursorPosition :: m ()
- showCursor :: m ()
- hideCursor :: m ()
- clearLine :: m ()
- clearLineLeft :: m ()
- clearLineRight :: m ()
- clearScreen :: m ()
- clearScreenAbove :: m ()
- clearScreenBelow :: m ()
- getScreenSize :: m (Int, Int)
- useAlternateScreenBuffer :: Bool -> m ()
- class MonadIO m => MonadInput m where
- waitMapInterruptAndEvents :: (STM () -> STM Event -> STM a) -> m a
- waitEvent :: MonadInput m => m Event
- waitEventOrElse :: MonadInput m => STM a -> m (Either Event a)
- waitInterruptOrElse :: MonadInput m => STM a -> m (Maybe a)
- data Event
- data Key
- data Direction
- data Modifiers
- shiftKey :: Modifiers
- ctrlKey :: Modifiers
- altKey :: Modifiers
- metaKey :: Modifiers
- data MouseEvent
- = MouseMoved (Int, Int)
- | MouseButtonPressed (Int, Int) MouseButton
- | MouseButtonReleased (Int, Int) MouseButton
- | MouseButtonClicked (Int, Int) MouseButton
- | MouseWheeled (Int, Int) Direction
- data MouseButton
- data WindowEvent
- data DeviceEvent
- data Terminal = Terminal {
- termType :: ByteString
- termInput :: STM Event
- termOutput :: Text -> STM ()
- termInterrupt :: STM ()
- termFlush :: STM ()
- termScreenSize :: STM (Int, Int)
- termSpecialChars :: Char -> Maybe Event
- newtype Decoder = Decoder {
- feedDecoder :: Modifiers -> Char -> ([Event], Decoder)
- ansiDecoder :: (Char -> Maybe Event) -> Decoder
Getting started
TerminalT
Instances
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 longTexts.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,MonadFormatPrinterandMonadColorPrinter. 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
Methods
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 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.
Instances
| (MonadIO m, MonadThrow m) => MonadPrinter (TerminalT m) Source # | |
Defined in Control.Monad.Terminal.TerminalT Methods putLn :: TerminalT m () Source # putChar :: Char -> TerminalT m () Source # putString :: String -> TerminalT m () Source # putStringLn :: String -> TerminalT m () Source # putText :: Text -> TerminalT m () Source # putTextLn :: Text -> TerminalT m () Source # flush :: TerminalT m () Source # getLineWidth :: TerminalT m Int Source # | |
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.
Minimal complete definition
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
resetAnnotationson 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
boldorunderlinedshall 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$brightBlue) >>resetAnnotation(foreground$dullRed)
results in the foreground color attribute reset afterwards whereas after
setAnnotation(foreground$brightBlue) >>resetAnnotation(background$dullRed)
resetAnnotations :: m () Source #
Reset all annotations to their default.
Instances
| (MonadIO m, MonadThrow m) => MonadPrettyPrinter (TerminalT m) Source # | |
Defined in Control.Monad.Terminal.TerminalT Associated Types data Annotation (TerminalT m) :: Type Source # Methods putDoc :: Doc (Annotation (TerminalT m)) -> TerminalT m () Source # putDocLn :: Doc (Annotation (TerminalT m)) -> TerminalT m () Source # setAnnotation :: Annotation (TerminalT m) -> TerminalT m () Source # resetAnnotation :: Annotation (TerminalT m) -> TerminalT m () Source # resetAnnotations :: TerminalT m () Source # | |
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.
Instances
| (MonadIO m, MonadThrow m) => MonadFormatPrinter (TerminalT m) Source # | |
Defined in Control.Monad.Terminal.TerminalT Methods bold :: Annotation (TerminalT m) Source # italic :: Annotation (TerminalT m) Source # underlined :: Annotation (TerminalT m) Source # | |
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
resetAnnotationinstead.
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.
Instances
| (MonadIO m, MonadThrow m) => MonadColorPrinter (TerminalT m) Source # | |
Defined in Control.Monad.Terminal.TerminalT Methods inverted :: Annotation (TerminalT m) Source # foreground :: Color -> Annotation (TerminalT m) Source # background :: Color -> Annotation (TerminalT m) Source # | |
dull :: BasicColor -> Color Source #
bright :: BasicColor -> Color Source #
data BasicColor Source #
Instances
| Eq BasicColor Source # | |
Defined in Control.Monad.Terminal.Printer | |
| Ord BasicColor Source # | |
Defined in Control.Monad.Terminal.Printer Methods compare :: BasicColor -> BasicColor -> Ordering # (<) :: BasicColor -> BasicColor -> Bool # (<=) :: BasicColor -> BasicColor -> Bool # (>) :: BasicColor -> BasicColor -> Bool # (>=) :: BasicColor -> BasicColor -> Bool # max :: BasicColor -> BasicColor -> BasicColor # min :: BasicColor -> BasicColor -> BasicColor # | |
| Show BasicColor Source # | |
Defined in Control.Monad.Terminal.Printer Methods showsPrec :: Int -> BasicColor -> ShowS # show :: BasicColor -> String # showList :: [BasicColor] -> ShowS # | |
Constructors
| Color ColorMode BasicColor |
Instances
| Eq ColorMode Source # | |
| Ord ColorMode Source # | |
| Show ColorMode Source # | |
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.
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.
Instances
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
UserInterruptto the seemingly unresponsive computation. - When an interrupt is signaled through the flag, an
InterruptEventmust 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 # | |
Defined in Control.Monad.Terminal.TerminalT | |
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 andwaitInterruptOrElseshould 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 andwaitInterruptOrElseshould be considered then.
waitInterruptOrElse
waitInterruptOrElse :: MonadInput m => STM a -> m (Maybe a) Source #
Wait simultaneously for the next interrupt or a given transaction.
- Returns
Nothingon interrupt andJustwhen 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
InterruptEventare flushed from the event stream in case of an interrupt.
Events
Constructors
| KeyEvent Key Modifiers | |
| MouseEvent MouseEvent | |
| WindowEvent WindowEvent | |
| DeviceEvent DeviceEvent | |
| InterruptEvent | |
| OtherEvent String |
Keys & Modifiers
Constructors
| CharKey Char | |
| TabKey | |
| SpaceKey | |
| BackspaceKey | |
| EnterKey | |
| InsertKey | |
| DeleteKey | |
| HomeKey | Pos 1 |
| BeginKey | |
| EndKey | |
| PageUpKey | |
| PageDownKey | |
| EscapeKey | |
| PrintKey | |
| PauseKey | |
| ArrowKey Direction | |
| FunctionKey Int |
Constructors
| Upwards | |
| Downwards | |
| Leftwards | |
| Rightwards |
Instances
| Eq Direction Source # | |
| Ord Direction Source # | |
| Show Direction Source # | |
Instances
| Eq Modifiers Source # | |
| Ord Modifiers Source # | |
| Show Modifiers Source # | |
| Semigroup Modifiers Source # | |
| Monoid Modifiers Source # | |
| Bits Modifiers Source # | |
Defined in Control.Monad.Terminal.Input Methods (.&.) :: Modifiers -> Modifiers -> Modifiers # (.|.) :: Modifiers -> Modifiers -> Modifiers # xor :: Modifiers -> Modifiers -> Modifiers # complement :: Modifiers -> Modifiers # shift :: Modifiers -> Int -> Modifiers # rotate :: Modifiers -> Int -> Modifiers # setBit :: Modifiers -> Int -> Modifiers # clearBit :: Modifiers -> Int -> Modifiers # complementBit :: Modifiers -> Int -> Modifiers # testBit :: Modifiers -> Int -> Bool # bitSizeMaybe :: Modifiers -> Maybe Int # isSigned :: Modifiers -> Bool # shiftL :: Modifiers -> Int -> Modifiers # unsafeShiftL :: Modifiers -> Int -> Modifiers # shiftR :: Modifiers -> Int -> Modifiers # unsafeShiftR :: Modifiers -> Int -> Modifiers # rotateL :: Modifiers -> Int -> Modifiers # | |
Mouse Events
data MouseEvent Source #
Constructors
| MouseMoved (Int, Int) | |
| MouseButtonPressed (Int, Int) MouseButton | |
| MouseButtonReleased (Int, Int) MouseButton | |
| MouseButtonClicked (Int, Int) MouseButton | |
| MouseWheeled (Int, Int) Direction |
Instances
| Eq MouseEvent Source # | |
Defined in Control.Monad.Terminal.Input | |
| Ord MouseEvent Source # | |
Defined in Control.Monad.Terminal.Input Methods compare :: MouseEvent -> MouseEvent -> Ordering # (<) :: MouseEvent -> MouseEvent -> Bool # (<=) :: MouseEvent -> MouseEvent -> Bool # (>) :: MouseEvent -> MouseEvent -> Bool # (>=) :: MouseEvent -> MouseEvent -> Bool # max :: MouseEvent -> MouseEvent -> MouseEvent # min :: MouseEvent -> MouseEvent -> MouseEvent # | |
| Show MouseEvent Source # | |
Defined in Control.Monad.Terminal.Input Methods showsPrec :: Int -> MouseEvent -> ShowS # show :: MouseEvent -> String # showList :: [MouseEvent] -> ShowS # | |
data MouseButton Source #
Constructors
| LeftMouseButton | |
| RightMouseButton | |
| OtherMouseButton |
Instances
| Eq MouseButton Source # | |
Defined in Control.Monad.Terminal.Input | |
| Ord MouseButton Source # | |
Defined in Control.Monad.Terminal.Input Methods compare :: MouseButton -> MouseButton -> Ordering # (<) :: MouseButton -> MouseButton -> Bool # (<=) :: MouseButton -> MouseButton -> Bool # (>) :: MouseButton -> MouseButton -> Bool # (>=) :: MouseButton -> MouseButton -> Bool # max :: MouseButton -> MouseButton -> MouseButton # min :: MouseButton -> MouseButton -> MouseButton # | |
| Show MouseButton Source # | |
Defined in Control.Monad.Terminal.Input Methods showsPrec :: Int -> MouseButton -> ShowS # show :: MouseButton -> String # showList :: [MouseButton] -> ShowS # | |
Window Events
data WindowEvent Source #
Constructors
| WindowLostFocus | |
| WindowGainedFocus | |
| WindowSizeChanged (Int, Int) |
Instances
| Eq WindowEvent Source # | |
Defined in Control.Monad.Terminal.Input | |
| Ord WindowEvent Source # | |
Defined in Control.Monad.Terminal.Input Methods compare :: WindowEvent -> WindowEvent -> Ordering # (<) :: WindowEvent -> WindowEvent -> Bool # (<=) :: WindowEvent -> WindowEvent -> Bool # (>) :: WindowEvent -> WindowEvent -> Bool # (>=) :: WindowEvent -> WindowEvent -> Bool # max :: WindowEvent -> WindowEvent -> WindowEvent # min :: WindowEvent -> WindowEvent -> WindowEvent # | |
| Show WindowEvent Source # | |
Defined in Control.Monad.Terminal.Input Methods showsPrec :: Int -> WindowEvent -> ShowS # show :: WindowEvent -> String # showList :: [WindowEvent] -> ShowS # | |
Device Events
data DeviceEvent Source #
Constructors
| DeviceAttributesReport String | |
| CursorPositionReport (Int, Int) |
Instances
| Eq DeviceEvent Source # | |
Defined in Control.Monad.Terminal.Input | |
| Ord DeviceEvent Source # | |
Defined in Control.Monad.Terminal.Input Methods compare :: DeviceEvent -> DeviceEvent -> Ordering # (<) :: DeviceEvent -> DeviceEvent -> Bool # (<=) :: DeviceEvent -> DeviceEvent -> Bool # (>) :: DeviceEvent -> DeviceEvent -> Bool # (>=) :: DeviceEvent -> DeviceEvent -> Bool # max :: DeviceEvent -> DeviceEvent -> DeviceEvent # min :: DeviceEvent -> DeviceEvent -> DeviceEvent # | |
| Show DeviceEvent Source # | |
Defined in Control.Monad.Terminal.Input Methods showsPrec :: Int -> DeviceEvent -> ShowS # show :: DeviceEvent -> String # showList :: [DeviceEvent] -> ShowS # | |
Low-Level
Terminal
Constructors
| Terminal | |
Fields
| |
Decoding
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.