| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Termbox.Tea
Description
This module provides an Elm Architecture interface to termbox, a simple C library for writing text-based user
interfaces: https://github.com/termbox/termbox
See also:
termbox-banana, areactive-bananaFRP interface.
👉 Quick start example
This termbox program displays the number of keys pressed.
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedRecordDot #-}
import Data.Foldable (fold)
import Data.Function ((&))
import Data.Void (Void)
import Termbox.Tea qualified as Termbox
main :: IO ()
main = do
result <-
Termbox.run
Termbox.Program
{ initialize,
pollEvent,
handleEvent,
render,
finished
}
putStrLn case result of
Left err -> "Termbox program failed to initialize: " ++ show err
Right state -> "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
render :: MyState -> Termbox.Scene
render state =
fold
[ string ("Number of keys pressed: " ++ show state.keysPressed),
fold
[ string "Press",
string "Esc" & Termbox.bold & Termbox.atCol 6,
string "to quit." & Termbox.atCol 10
]
& Termbox.atRow 2
]
& Termbox.at Termbox.Pos {row = 2, col = 4}
& Termbox.image
finished :: MyState -> Bool
finished state =
state.pressedEsc
string :: [Char] -> Termbox.Image
string chars =
zip [0 ..] chars & foldMap \(i, char) ->
Termbox.char char & Termbox.atCol i
Synopsis
- data Program s = forall e.Program {}
- run :: Program s -> IO (Either InitError s)
- data InitError
- data Scene
- image :: Image -> Scene
- fill :: Color -> Scene -> Scene
- cursor :: Pos -> Scene -> Scene
- data Image
- char :: Char -> Image
- fg :: Color -> Image -> Image
- bg :: Color -> Image -> Image
- bold :: Image -> Image
- underline :: Image -> Image
- blink :: Image -> Image
- at :: Pos -> Image -> Image
- atRow :: Int -> Image -> Image
- atCol :: Int -> Image -> Image
- 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
- | 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 KeyCtrlUnderscore :: Key
- pattern KeyCtrlI :: Key
- pattern KeyCtrlM :: Key
- pattern KeyCtrl7 :: Key
- pattern KeyCtrl5 :: Key
- pattern KeyCtrl4 :: Key
- pattern KeyCtrl3 :: Key
- pattern KeyCtrl2 :: Key
- pattern KeyCtrlLsqBracket :: Key
- pattern KeyCtrlH :: Key
- data Mouse = Mouse {
- button :: !MouseButton
- pos :: !Pos
- data MouseButton where
- pattern WheelUp :: MouseButton
- pattern WheelDown :: MouseButton
- pattern ReleaseClick :: MouseButton
- pattern RightClick :: MouseButton
- pattern MiddleClick :: MouseButton
- pattern LeftClick :: MouseButton
- data Pos = Pos {}
- posUp :: Int -> Pos -> Pos
- posDown :: Int -> Pos -> Pos
- posLeft :: Int -> Pos -> Pos
- posRight :: Int -> Pos -> Pos
- data Size = Size {}
Main
A termbox program, parameterized by state s.
Constructors
| forall e. Program | |
Fields
| |
run :: Program s -> IO (Either InitError s) Source #
Run a termbox program.
run either:
- Returns immediately with an
InitError. - Returns the final state, once it's
finished.
termbox initialization errors.
Constructors
| FailedToOpenTTY | |
| PipeTrapError | |
| UnsupportedTerminal |
Instances
| Exception InitError | |
Defined in Termbox.Internal.Main Methods toException :: InitError -> SomeException # fromException :: SomeException -> Maybe InitError # displayException :: InitError -> String # | |
| Show InitError | |
Terminal contents
Scene
Image
Create an image from a character.
If the character is not 1 character wide, it will not be displayed.
Color
Style
Translation
Colors
A color.
There are three classes of colors:
Basic colors
defaultColor :: Color #
216 miscellaneous colors
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 | Mouse event |
| EventUser !e | User event |
Instances
| Generic (Event e) | |
| Show e => Show (Event e) | |
| Eq e => Eq (Event e) | |
| type Rep (Event e) | |
Defined in Termbox.Internal.Event type Rep (Event e) = D1 ('MetaData "Event" "Termbox.Internal.Event" "termbox-2.0.0-inplace" '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)) :+: 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 KeyCtrlUnderscore :: Key | |
| pattern KeyCtrlI :: Key | |
| pattern KeyCtrlM :: Key | |
| pattern KeyCtrl7 :: Key | |
| pattern KeyCtrl5 :: Key | |
| pattern KeyCtrl4 :: Key | |
| pattern KeyCtrl3 :: Key | |
| pattern KeyCtrl2 :: Key | |
| pattern KeyCtrlLsqBracket :: Key | |
| pattern KeyCtrlH :: Key |
A mouse event.
Constructors
| Mouse | |
Fields
| |
Instances
| Generic Mouse | |
| Show Mouse | |
| Eq Mouse | |
| Ord Mouse | |
| type Rep Mouse | |
Defined in Termbox.Internal.Mouse type Rep Mouse = D1 ('MetaData "Mouse" "Termbox.Internal.Mouse" "termbox-2.0.0-inplace" 'False) (C1 ('MetaCons "Mouse" 'PrefixI 'True) (S1 ('MetaSel ('Just "button") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 MouseButton) :*: S1 ('MetaSel ('Just "pos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos))) | |
data MouseButton where #
A mouse button.
Bundled Patterns
| pattern WheelUp :: MouseButton | |
| pattern WheelDown :: MouseButton | |
| pattern ReleaseClick :: MouseButton | |
| pattern RightClick :: MouseButton | |
| pattern MiddleClick :: MouseButton | |
| pattern LeftClick :: MouseButton |
Instances
| Show MouseButton | |
Defined in Termbox.Internal.Mouse Methods showsPrec :: Int -> MouseButton -> ShowS # show :: MouseButton -> String # showList :: [MouseButton] -> ShowS # | |
| Eq MouseButton | |
Defined in Termbox.Internal.Mouse | |
| Ord MouseButton | |
Defined in Termbox.Internal.Mouse 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 # | |
Miscellaneous types
A relative terminal position.
Instances
| Monoid Pos | |
| Semigroup Pos | |
| Generic Pos | |
| Show Pos | |
| Eq Pos | |
| Ord Pos | |
| type Rep Pos | |
Defined in Termbox.Internal.Pos type Rep Pos = D1 ('MetaData "Pos" "Termbox.Internal.Pos" "termbox-2.0.0-inplace" 'False) (C1 ('MetaCons "Pos" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Just "col") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int))) | |
A terminal size.
Instances
| Generic Size | |
| Show Size | |
| Eq Size | |
| Ord Size | |
| type Rep Size | |
Defined in Termbox.Internal.Size type Rep Size = D1 ('MetaData "Size" "Termbox.Internal.Size" "termbox-2.0.0-inplace" 'False) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "width") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int))) | |