Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- withTerminal :: (MonadIO m, MonadMask m) => (LocalTerminal -> m a) -> m a
- runTerminalT :: (MonadIO m, MonadMask m, Terminal t) => TerminalT t m a -> t -> m a
- data TerminalT t m a
- class Monad m => MonadPrinter m where
- class MonadPrinter m => MonadMarkupPrinter m where
- data Attribute m
- setAttribute :: Attribute m -> m ()
- resetAttribute :: Attribute m -> m ()
- resetAttributes :: m ()
- resetsAttribute :: Attribute m -> Attribute m -> Bool
- class MonadMarkupPrinter m => MonadFormattingPrinter m where
- class MonadMarkupPrinter m => MonadColorPrinter m where
- putDoc :: MonadMarkupPrinter m => Doc (Attribute m) -> m ()
- putDocLn :: MonadMarkupPrinter m => Doc (Attribute m) -> m ()
- putPretty :: (MonadMarkupPrinter m, Pretty a) => a -> m ()
- putPrettyLn :: (MonadMarkupPrinter m, Pretty a) => a -> m ()
- putSimpleDocStream :: MonadMarkupPrinter m => SimpleDocStream (Attribute m) -> m ()
- class MonadPrinter m => MonadScreen m where
- getWindowSize :: m Size
- moveCursorUp :: Int -> m ()
- moveCursorDown :: Int -> m ()
- moveCursorForward :: Int -> m ()
- moveCursorBackward :: Int -> m ()
- getCursorPosition :: m Position
- setCursorPosition :: Position -> m ()
- setCursorRow :: Int -> m ()
- setCursorColumn :: Int -> m ()
- saveCursor :: m ()
- restoreCursor :: m ()
- insertChars :: Int -> m ()
- deleteChars :: Int -> m ()
- eraseChars :: Int -> m ()
- insertLines :: Int -> m ()
- deleteLines :: Int -> m ()
- eraseInLine :: EraseMode -> m ()
- eraseInDisplay :: EraseMode -> m ()
- showCursor :: m ()
- hideCursor :: m ()
- setAutoWrap :: Bool -> m ()
- setAlternateScreenBuffer :: Bool -> m ()
- data Size = Size {}
- data Position = Position {}
- data EraseMode
- class (MonadInput m, MonadFormattingPrinter m, MonadColorPrinter m, MonadScreen m) => MonadTerminal m
- class MonadIO m => MonadInput m where
- awaitEvent :: MonadInput m => m (Either Interrupt Event)
- checkInterrupt :: MonadInput m => m Bool
- data Event
- data Interrupt = Interrupt
- data Key
- data Modifiers
- shiftKey :: Modifiers
- ctrlKey :: Modifiers
- altKey :: Modifiers
- metaKey :: Modifiers
- data Direction
- data MouseEvent
- data MouseButton
- data WindowEvent
- data DeviceEvent
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
doputTextLn
"Hello there, please press a button!"flush
ev <-waitEvent
putStringLn
$ "Event was " ++ show evflush
TerminalT
runTerminalT :: (MonadIO m, MonadMask m, Terminal t) => TerminalT t m a -> t -> m a Source #
Run a TerminalT
application on the given terminal.
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 = doputTextLn
"Hello world!"flush
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
String
s and longText
s.String
s 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.
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 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, Terminal t) => MonadPrinter (TerminalT t m) Source # | |
Defined in System.Terminal.TerminalT putLn :: TerminalT t m () Source # putChar :: Char -> TerminalT t m () Source # putString :: String -> TerminalT t m () Source # putStringLn :: String -> TerminalT t m () Source # putText :: Text -> TerminalT t m () Source # putTextLn :: Text -> TerminalT t m () Source # flush :: TerminalT t m () Source # getLineWidth :: TerminalT t m Int Source # |
MonadMarkupPrinter
class MonadPrinter m => MonadMarkupPrinter m where Source #
This class introduces abstract constructors for text markup.
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.
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
orunderlined
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
)
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.
Instances
(MonadIO m, MonadThrow m, Terminal t) => MonadMarkupPrinter (TerminalT t m) Source # | |
Defined in System.Terminal.TerminalT |
MonadFormattingPrinter
class MonadMarkupPrinter m => MonadFormattingPrinter m where 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.
Instances
(MonadIO m, MonadThrow m, Terminal t) => MonadFormattingPrinter (TerminalT t m) Source # | |
MonadColorPrinter
class MonadMarkupPrinter m => MonadColorPrinter m where Source #
This class offers abstract value constructors for foreground and background coloring.
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.
Instances
(MonadIO m, MonadThrow m, Terminal t) => MonadColorPrinter (TerminalT t m) Source # | |
Defined in System.Terminal.TerminalT black :: Color (TerminalT t m) Source # red :: Color (TerminalT t m) Source # green :: Color (TerminalT t m) Source # yellow :: Color (TerminalT t m) Source # blue :: Color (TerminalT t m) Source # magenta :: Color (TerminalT t m) Source # cyan :: Color (TerminalT t m) Source # white :: Color (TerminalT t m) Source # bright :: Color (TerminalT t m) -> Color (TerminalT t m) Source # foreground :: Color (TerminalT t m) -> Attribute (TerminalT t m) Source # background :: Color (TerminalT t m) -> Attribute (TerminalT t m) Source # |
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 SimpleDocStream
s (rather internal and not for the average user).
MonadScreen
class MonadPrinter m => MonadScreen m where Source #
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
andrestoreCursor
!
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.
Instances
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 # | |
Defined in System.Terminal.TerminalT |
Event Processing
class MonadIO m => MonadInput m where Source #
This monad describes an environment that maintains a stream of Event
s
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.
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).
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
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 (likea
,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 forCtrl+C
when you meanInterrupt
! Example: The tab key will likely emitKeyEvent (CharKey
andI
) ctrlKeyKeyEvent TabKey mempty
in most settings.
KeyEvent Key Modifiers | |
MouseEvent MouseEvent | |
WindowEvent WindowEvent | |
DeviceEvent DeviceEvent | |
OtherEvent String |
Interrupt is a special type of event that needs to be treated with priority. It is therefor not included in the regular event stream.
Keys & Modifiers
Events triggered by key press.
CharKey Char | |
TabKey | |
SpaceKey | |
BackspaceKey | |
EnterKey | |
InsertKey | |
DeleteKey | |
HomeKey | |
BeginKey | |
EndKey | |
PageUpKey | |
PageDownKey | |
EscapeKey | |
PrintKey | |
PauseKey | |
ArrowKey Direction | |
FunctionKey Int |
Modifier keys.
Instances
Eq Modifiers Source # | |
Ord Modifiers Source # | |
Defined in System.Terminal.MonadInput | |
Show Modifiers Source # | |
Semigroup Modifiers Source # | |
Monoid Modifiers Source # | |
Bits Modifiers Source # | |
Defined in System.Terminal.MonadInput (.&.) :: 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 #
Events triggered by mouse action.
- Mouse event reporting must be activated before (TODO).
MouseMoved Position | |
MouseButtonPressed Position MouseButton | |
MouseButtonReleased Position MouseButton | |
MouseButtonClicked Position MouseButton | |
MouseWheeled Position Direction |
Instances
Eq MouseEvent Source # | |
Defined in System.Terminal.MonadInput (==) :: MouseEvent -> MouseEvent -> Bool # (/=) :: MouseEvent -> MouseEvent -> Bool # | |
Ord MouseEvent Source # | |
Defined in System.Terminal.MonadInput 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 System.Terminal.MonadInput showsPrec :: Int -> MouseEvent -> ShowS # show :: MouseEvent -> String # showList :: [MouseEvent] -> ShowS # |
data MouseButton Source #
Instances
Eq MouseButton Source # | |
Defined in System.Terminal.MonadInput (==) :: MouseButton -> MouseButton -> Bool # (/=) :: MouseButton -> MouseButton -> Bool # | |
Ord MouseButton Source # | |
Defined in System.Terminal.MonadInput 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 System.Terminal.MonadInput showsPrec :: Int -> MouseButton -> ShowS # show :: MouseButton -> String # showList :: [MouseButton] -> ShowS # |
Window Events
data WindowEvent Source #
Instances
Eq WindowEvent Source # | |
Defined in System.Terminal.MonadInput (==) :: WindowEvent -> WindowEvent -> Bool # (/=) :: WindowEvent -> WindowEvent -> Bool # | |
Ord WindowEvent Source # | |
Defined in System.Terminal.MonadInput 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 System.Terminal.MonadInput showsPrec :: Int -> WindowEvent -> ShowS # show :: WindowEvent -> String # showList :: [WindowEvent] -> ShowS # |
Device Events
data DeviceEvent Source #
Instances
Eq DeviceEvent Source # | |
Defined in System.Terminal.MonadInput (==) :: DeviceEvent -> DeviceEvent -> Bool # (/=) :: DeviceEvent -> DeviceEvent -> Bool # | |
Ord DeviceEvent Source # | |
Defined in System.Terminal.MonadInput 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 System.Terminal.MonadInput showsPrec :: Int -> DeviceEvent -> ShowS # show :: DeviceEvent -> String # showList :: [DeviceEvent] -> ShowS # |