Safe Haskell | None |
---|---|
Language | Haskell2010 |
A termbox
program is typically constructed as an infinite loop that:
- Renders a scene.
- Polls for an event.
For example, this progam simply displays the number of keys pressed, and
quits on Esc
:
{-# LANGUAGE LambdaCase #-} import qualified Termbox main :: IO () main = Termbox.run
(\_width _height render poll -> loop render poll 0) loop :: (Termbox.Cells
-> Termbox.Cursor
-> IO ()) -> IO Termbox.Event
-> Int -> IO () loop render poll n = do render (string (show n)) Termbox.NoCursor
poll >>= \case Termbox.EventKey
Termbox.KeyEsc
-> pure () _ -> loop render poll (n+1) string :: Int -> Int -> String -> Termbox.Cells
string col row = foldMap (\(i, c) -> Termbox.set
(col + i) row (Termbox.Cell
c 0 0)) . zip [0..]
Other termbox features include cell attributes (style, color), cursor display, and mouse click handling.
This module is intended to be imported qualified.
Synopsis
- run :: (Int -> Int -> (Cells -> Cursor -> IO ()) -> IO Event -> IO a) -> IO a
- data InitError
- set :: Int -> Int -> Cell -> Cells
- data Cells
- data Cell = Cell !Char !Attr !Attr
- data Cursor
- data Event
- = EventKey !Key
- | EventResize !Int !Int
- | EventMouse !Mouse !Int !Int
- data Key
- = KeyChar Char
- | KeyArrowDown
- | KeyArrowLeft
- | KeyArrowRight
- | KeyArrowUp
- | KeyBackspace
- | KeyCtrlBackspace
- | KeyCtrl6
- | KeyCtrl8
- | KeyCtrlA
- | KeyCtrlB
- | KeyCtrlBackslash
- | KeyCtrlC
- | KeyCtrlD
- | KeyCtrlE
- | KeyCtrlF
- | KeyCtrlG
- | KeyCtrlJ
- | KeyCtrlK
- | KeyCtrlL
- | KeyCtrlN
- | KeyCtrlO
- | KeyCtrlP
- | KeyCtrlQ
- | KeyCtrlR
- | KeyCtrlRsqBracket
- | KeyCtrlS
- | KeyCtrlSlash
- | KeyCtrlTilde
- | KeyCtrlT
- | KeyCtrlU
- | 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
- pattern KeyCtrlH :: Key
- pattern KeyCtrlLsqBracket :: Key
- pattern KeyCtrl2 :: Key
- pattern KeyCtrl3 :: Key
- pattern KeyCtrl4 :: Key
- pattern KeyCtrl5 :: Key
- pattern KeyCtrl7 :: Key
- pattern KeyCtrlM :: Key
- pattern KeyCtrlI :: Key
- pattern KeyCtrlUnderscore :: Key
- data Mouse
- data PollError = PollError
- data Attr
- black :: Attr
- red :: Attr
- green :: Attr
- yellow :: Attr
- blue :: Attr
- magenta :: Attr
- cyan :: Attr
- white :: Attr
- bold :: Attr
- underline :: Attr
- reverse :: Attr
Initialization
run :: (Int -> Int -> (Cells -> Cursor -> IO ()) -> IO Event -> IO a) -> IO a Source #
Run a termbox
program and restore the terminal state afterwards.
The function provided to run
is provided:
- The initial terminal width
- The initial terminal height
- An action that renders a scene
- An action that polls for an event indefinitely
Throws: InitError
Termbox initialization errors.
Instances
Show InitError Source # | |
Exception InitError Source # | |
Defined in Termbox toException :: InitError -> SomeException # fromException :: SomeException -> Maybe InitError # displayException :: InitError -> String # |
Terminal contents
A cell contains a character, foreground attribute, and background attribute.
Event handling
A input event.
EventKey !Key | Key event |
EventResize !Int !Int | Resize event (width, then height) |
EventMouse !Mouse !Int !Int | Mouse event (column, then row) |
A key event.
KeyChar Char | |
KeyArrowDown | |
KeyArrowLeft | |
KeyArrowRight | |
KeyArrowUp | |
KeyBackspace | |
KeyCtrlBackspace | Also: |
KeyCtrl6 | |
KeyCtrl8 | |
KeyCtrlA | |
KeyCtrlB | |
KeyCtrlBackslash | Also: |
KeyCtrlC | |
KeyCtrlD | |
KeyCtrlE | |
KeyCtrlF | |
KeyCtrlG | |
KeyCtrlJ | |
KeyCtrlK | |
KeyCtrlL | |
KeyCtrlN | |
KeyCtrlO | |
KeyCtrlP | |
KeyCtrlQ | |
KeyCtrlR | |
KeyCtrlRsqBracket | Also: |
KeyCtrlS | |
KeyCtrlSlash | Also: |
KeyCtrlTilde | Also: |
KeyCtrlT | |
KeyCtrlU | |
KeyCtrlV | |
KeyCtrlW | |
KeyCtrlX | |
KeyCtrlY | |
KeyCtrlZ | |
KeyDelete | |
KeyEnd | |
KeyEnter | Also: |
KeyEsc | Also: |
KeyF1 | |
KeyF10 | |
KeyF11 | |
KeyF12 | |
KeyF2 | |
KeyF3 | |
KeyF4 | |
KeyF5 | |
KeyF6 | |
KeyF7 | |
KeyF8 | |
KeyF9 | |
KeyHome | |
KeyInsert | |
KeyPageDn | |
KeyPageUp | |
KeySpace | |
KeyTab | Also: |
In a few cases, distinct key sequences map to equivalent key events. The pattern synonyms below are provided for an alternate syntax in these cases, if desired.
pattern KeyCtrlLsqBracket :: Key Source #
pattern KeyCtrlUnderscore :: Key Source #
An error occurred when polling, due to mysterious circumstances that are not well-documented in the original C codebase.
Instances
Show PollError Source # | |
Exception PollError Source # | |
Defined in Termbox.Event 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.