| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Termbox
Description
This module provides a high-level wrapper around termbox, a simple C library for writing text-based user
interfaces: https://github.com/termbox/termbox
This module is intended to be imported qualified.
👉 Quick start example
This termbox program displays the number of keys pressed.
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoFieldSelectors #-}
import Data.Foldable (fold)
import Data.Void (Void)
import Termbox qualified
main :: IO ()
main = do
result <-
Termbox.run
Termbox.Program
{ initialize,
pollEvent,
handleEvent,
handleEventError,
render,
finished
}
case result of
Left err -> putStrLn ("Termbox program failed to initialize: " ++ show err)
Right state -> putStrLn ("Final state: " ++ show state)
data MyState = MyState
{ keysPressed :: Int,
pressedEsc :: Bool
}
deriving stock (Show)
initialize :: Termbox.Size -> MyState
initialize _size =
MyState
{ keysPressed = 0,
pressedEsc = False
}
pollEvent :: Maybe (IO Void)
pollEvent =
Nothing
handleEvent :: MyState -> Termbox.Event Void -> IO MyState
handleEvent state = \case
Termbox.EventKey key ->
pure
MyState
{ keysPressed = state.keysPressed + 1,
pressedEsc =
case key of
Termbox.KeyEsc -> True
_ -> False
}
_ -> pure state
handleEventError :: MyState -> IO MyState
handleEventError state =
pure state
render :: MyState -> Termbox.Scene
render state =
fold
[ string
Termbox.Pos {row = 2, col = 4}
("Number of keys pressed: " ++ map Termbox.char (show state.keysPressed))
, string
Termbox.Pos {row = 4, col = 4}
("Press " ++ map (Termbox.bold . Termbox.char) Esc ++ " to quit.")
]
finished :: MyState -> Bool
finished state =
state.pressedEsc
string :: Termbox.Pos -> [Termbox.Cell] -> Termbox.Scene
string pos cells =
foldMap
(\(i, cell) ->
Termbox.cell
Termbox.Pos {row = pos.row, col = pos.col + i}
cell)
(zip [0 ..] cells)
Synopsis
- data Program s = forall e.Program {}
- run :: Program s -> IO (Either InitError s)
- data InitError
- data Scene
- cell :: Pos -> Cell -> Scene
- fill :: Color -> Scene
- cursor :: Pos -> Scene
- data Cell
- char :: Char -> Cell
- fg :: Color -> Cell -> Cell
- bg :: Color -> Cell -> Cell
- bold :: Cell -> Cell
- underline :: Cell -> Cell
- blink :: Cell -> Cell
- data Color
- defaultColor :: Color
- red :: Color
- green :: Color
- yellow :: Color
- blue :: Color
- magenta :: Color
- cyan :: Color
- white :: Color
- bright :: Color -> Color
- color :: Int -> Color
- gray :: Int -> Color
- data Event e
- = EventKey !Key
- | EventResize !Size
- | EventMouse !Mouse !Pos
- | EventUser !e
- data Key where
- 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 where
- pattern MouseLeft :: Mouse
- pattern MouseMiddle :: Mouse
- pattern MouseRelease :: Mouse
- pattern MouseRight :: Mouse
- pattern MouseWheelDown :: Mouse
- pattern MouseWheelUp :: Mouse
- data Pos = Pos {}
- posUp :: Int -> Pos -> Pos
- posDown :: Int -> Pos -> Pos
- posLeft :: Int -> Pos -> Pos
- posRight :: Int -> Pos -> Pos
- data Size = Size {}
Termbox
A termbox program, parameterized by state s.
Constructors
| forall e. Program | |
Fields
| |
run :: Program s -> IO (Either InitError s) Source #
Run a termbox program.
Either returns immediately with an InitError, or once the program state is finished with the final state.
termbox initialization errors.
Constructors
| FailedToOpenTTY | |
| PipeTrapError | |
| UnsupportedTerminal |
Instances
| Exception InitError Source # | |
Defined in Termbox Methods toException :: InitError -> SomeException # fromException :: SomeException -> Maybe InitError # displayException :: InitError -> String # | |
| Show InitError Source # | |
Terminal contents
Scene
Cell
A single cell.
Instances
| IsString [Cell] Source # | |
Defined in Termbox.Internal.Cell Methods fromString :: String -> [Cell] # | |
Create a cell from a character.
If the character is not 1 character wide, it will not be displayed.
Colors
Basic colors
defaultColor :: Color Source #
216 miscellaneous colors
color :: Int -> Color Source #
A miscellaneous color.
Valid values are in the range [0, 215]; values outside of this range are clamped.
24 monochrome colors
A monochrome color; black is 0 and white is 23.
Valid values are in the range [0, 23]; values outside of this range are clamped.
Event handling
An input event.
Constructors
| EventKey !Key | Key event |
| EventResize !Size | Resize event |
| EventMouse !Mouse !Pos | Mouse event |
| EventUser !e | User event |
Instances
| Generic (Event e) Source # | |
| Show e => Show (Event e) Source # | |
| Eq e => Eq (Event e) Source # | |
| type Rep (Event e) Source # | |
Defined in Termbox.Internal.Event type Rep (Event e) = D1 ('MetaData "Event" "Termbox.Internal.Event" "termbox-1.0.0-DPWGBoIlJyKFQWwmcVdGn9" 'False) ((C1 ('MetaCons "EventKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Key)) :+: C1 ('MetaCons "EventResize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size))) :+: (C1 ('MetaCons "EventMouse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Mouse) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos)) :+: C1 ('MetaCons "EventUser" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 e)))) | |
A key event.
Some distinct key sequences map to the same key event. For example, to a termbox program, Enter is
indistinguishable from Ctrl+M. Pattern synonyms below are provided for an alternate syntax in these cases, if
desired.
Constructors
Bundled Patterns
| 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 |
A mouse event.
Bundled Patterns
| pattern MouseLeft :: Mouse | |
| pattern MouseMiddle :: Mouse | |
| pattern MouseRelease :: Mouse | |
| pattern MouseRight :: Mouse | |
| pattern MouseWheelDown :: Mouse | |
| pattern MouseWheelUp :: Mouse |
Miscellaneous types
A terminal position.
Instances
| Generic Pos Source # | |
| Show Pos Source # | |
| Eq Pos Source # | |
| Ord Pos Source # | |
| type Rep Pos Source # | |
Defined in Termbox.Internal.Pos type Rep Pos = D1 ('MetaData "Pos" "Termbox.Internal.Pos" "termbox-1.0.0-DPWGBoIlJyKFQWwmcVdGn9" 'False) (C1 ('MetaCons "Pos" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "col") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))) | |
A terminal size.
Instances
| Generic Size Source # | |
| Show Size Source # | |
| Eq Size Source # | |
| Ord Size Source # | |
| type Rep Size Source # | |
Defined in Termbox.Internal.Size type Rep Size = D1 ('MetaData "Size" "Termbox.Internal.Size" "termbox-1.0.0-DPWGBoIlJyKFQWwmcVdGn9" 'False) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "width") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))) | |