Safe Haskell | None |
---|---|
Language | Haskell2010 |
A termbox
program is typically constructed as an infinite loop that:
clear
s the terminal backbuffer.- Renders the program state by
set
ting individual pixels. flush
es the backbuffer to the terminal.poll
s for an event to update the program state.
For example, this progam simply displays the number of keys pressed, and
quits on Esc
:
{-# LANGUAGE LambdaCase #-} import Data.Foldable (for_) import qualified Termbox main :: IO () main = Termbox.run_
(loop 0) loop :: Int -> IO () loop n = do Termbox.clear
mempty mempty render n Termbox.flush
Termbox.poll
>>= \case Termbox.EventKey
Termbox.KeyEsc
_ -> pure () _ -> loop (n+1) render :: Int -> IO () render n = for_ (zip [0..] (show n)) (\(i, c) -> Termbox.set
i 0 (Termbox.Cell
c mempty mempty))
Other termbox features include cell attributes (style, color), cursor display, and mouse click handling.
This module is intended to be imported qualified.
Synopsis
- run :: IO a -> IO (Either InitError a)
- run_ :: IO a -> IO a
- data InitError
- set :: Int -> Int -> Cell -> IO ()
- getCells :: IO (Array (Int, Int) Cell)
- clear :: Attr -> Attr -> IO ()
- flush :: IO ()
- data Cell = Cell !Char !Attr !Attr
- getSize :: IO (Int, Int)
- setCursor :: Int -> Int -> IO ()
- hideCursor :: IO ()
- poll :: IO Event
- data Event
- = EventKey !Key !Bool
- | EventResize !Int !Int
- | EventMouse !Mouse !Int !Int
- data Key
- = KeyChar Char
- | KeyArrowDown
- | KeyArrowLeft
- | KeyArrowRight
- | KeyArrowUp
- | KeyBackspace
- | KeyBackspace2
- | KeyCtrl2
- | KeyCtrl3
- | KeyCtrl4
- | KeyCtrl5
- | KeyCtrl6
- | KeyCtrl7
- | KeyCtrl8
- | KeyCtrlA
- | KeyCtrlB
- | KeyCtrlBackslash
- | KeyCtrlC
- | KeyCtrlD
- | KeyCtrlE
- | KeyCtrlF
- | KeyCtrlG
- | KeyCtrlH
- | KeyCtrlI
- | KeyCtrlJ
- | KeyCtrlK
- | KeyCtrlL
- | KeyCtrlLsqBracket
- | KeyCtrlM
- | KeyCtrlN
- | KeyCtrlO
- | KeyCtrlP
- | KeyCtrlQ
- | KeyCtrlR
- | KeyCtrlRsqBracket
- | KeyCtrlS
- | KeyCtrlSlash
- | KeyCtrlT
- | KeyCtrlTilde
- | KeyCtrlU
- | KeyCtrlUnderscore
- | KeyCtrlV
- | KeyCtrlW
- | KeyCtrlX
- | KeyCtrlY
- | KeyCtrlZ
- | KeyDelete
- | KeyEnd
- | KeyEnter
- | KeyEsc
- | KeyF1
- | KeyF10
- | KeyF11
- | KeyF12
- | KeyF2
- | KeyF3
- | KeyF4
- | KeyF5
- | KeyF6
- | KeyF7
- | KeyF8
- | KeyF9
- | KeyHome
- | KeyInsert
- | KeyPageDn
- | KeyPageUp
- | KeySpace
- | KeyTab
- data Mouse
- data PollError = PollError
- black :: Attr
- red :: Attr
- green :: Attr
- yellow :: Attr
- blue :: Attr
- magenta :: Attr
- cyan :: Attr
- white :: Attr
- bold :: Attr
- underline :: Attr
- reverse :: Attr
- data Attr
- getInputMode :: HasCallStack => IO InputMode
- setInputMode :: InputMode -> IO ()
- data InputMode
- data MouseMode
- getOutputMode :: HasCallStack => IO OutputMode
- setOutputMode :: OutputMode -> IO ()
- data OutputMode
Initialization
run :: IO a -> IO (Either InitError a) Source #
Run a termbox
program and restore the terminal state afterwards.
Termbox initialization errors that can be returned by run
.
Instances
Show InitError Source # | |
Exception InitError Source # | |
Defined in Termbox toException :: InitError -> SomeException # fromException :: SomeException -> Maybe InitError # displayException :: InitError -> String # |
Terminal contents
set :: Int -> Int -> Cell -> IO () Source #
Set the cell at the given coordinates (column, then row).
getCells :: IO (Array (Int, Int) Cell) Source #
Get the terminal's two-dimensional array of cells (indexed by row, then column).
clear :: Attr -> Attr -> IO () Source #
Clear the back buffer with the given foreground and background attributes.
A Cell
contains a character, foreground attribute, and background
attribute.
Terminal size
Cursor manipulation
hideCursor :: IO () Source #
Hide the cursor.
Event handling
Block until an Event
arrives.
Note: termbox v1.1.2
does not properly handle OS signals that interrupt
the underlying select
system call, so unfortunately the familiar Ctrl-C
will not be able to stop a program stuck in pollEvent
.
You can work around this issue by polling in a background thread using the
threaded
runtime, or simply writing event-handling code that is responsive
to intuitive "quit" keys like q
and Esc
.
Throws: PollError
A input event.
EventKey !Key !Bool | Key event. The bool indicates the alt modifier. |
EventResize !Int !Int | Resize event (width, then height) |
EventMouse !Mouse !Int !Int | Mouse event (column, then row) |
A key event.
An error occurred when poll
ing, due to mysterious circumstances that are
not well-documented in the original C codebase.
Instances
Show PollError Source # | |
Exception PollError Source # | |
Defined in Termbox toException :: PollError -> SomeException # fromException :: SomeException -> Maybe PollError # displayException :: PollError -> String # |
Attributes
A cell attribute, which includes its color, and whether or not it is bold, underlined, and/or reversed.
A cell can only have one color, but may be (for example) bold and
underlined. The Monoid
instance combines Attr
s this way, with a right
bias.
Terminal modes
getInputMode :: HasCallStack => IO InputMode Source #
Get the current input mode.
setInputMode :: InputMode -> IO () Source #
Set the input mode.
The input modes.
- Esc. When ESC sequence is in the buffer and it doesn't match any known
sequence, ESC means
KeyEsc
. - Alt. When ESC sequence is in the buffer and it doesn't match any known sequence, ESC enables the alt modifier for the next keyboard event.
The mouse mode.
- No. Don't handle mouse events.
- Yes. Handle mouse events.
MouseModeNo | Default. |
MouseModeYes |
getOutputMode :: HasCallStack => IO OutputMode Source #
Get the current output mode.
setOutputMode :: OutputMode -> IO () Source #
Set the output mode.
data OutputMode Source #
The output modes.
- Normal. Supports colors 0..8, which includes all named color
attributes exported by this library, e.g.
red
. - Grayscale. Supports colors 0..23.
- 216. Supports colors 0..216.
- 256. Supports colors 0..255.
Instances
Eq OutputMode Source # | |
Defined in Termbox (==) :: OutputMode -> OutputMode -> Bool # (/=) :: OutputMode -> OutputMode -> Bool # | |
Ord OutputMode Source # | |
Defined in Termbox compare :: OutputMode -> OutputMode -> Ordering # (<) :: OutputMode -> OutputMode -> Bool # (<=) :: OutputMode -> OutputMode -> Bool # (>) :: OutputMode -> OutputMode -> Bool # (>=) :: OutputMode -> OutputMode -> Bool # max :: OutputMode -> OutputMode -> OutputMode # min :: OutputMode -> OutputMode -> OutputMode # | |
Show OutputMode Source # | |
Defined in Termbox showsPrec :: Int -> OutputMode -> ShowS # show :: OutputMode -> String # showList :: [OutputMode] -> ShowS # |