| 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
You may prefer to use one of the following interfaces instead:
termbox-banana, areactive-bananaFRP interface.termbox-tea, an Elm Architecture interface.
This module is intended to be imported qualified.
Synopsis
- run :: IO a -> IO (Either InitError a)
- initialize :: IO (Either InitError ())
- finalize :: IO ()
- data InitError
- data Scene
- render :: Scene -> IO ()
- 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
- | 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 = Mouse {
- button :: !MouseButton
- pos :: !Pos
- data MouseButton where
- pattern LeftClick :: MouseButton
- pattern MiddleClick :: MouseButton
- pattern ReleaseClick :: MouseButton
- pattern RightClick :: MouseButton
- pattern WheelDown :: MouseButton
- pattern WheelUp :: MouseButton
- poll :: IO (Event e)
- data Pos = Pos {}
- posUp :: Int -> Pos -> Pos
- posDown :: Int -> Pos -> Pos
- posLeft :: Int -> Pos -> Pos
- posRight :: Int -> Pos -> Pos
- data Size = Size {}
- getSize :: IO Size
Main
run :: IO a -> IO (Either InitError a) Source #
Initialize a termbox program, and if that succeeds, run the provided action, then finalize the termbox program.
initialize :: IO (Either InitError ()) Source #
Initialize a termbox program.
If initialize succeeds, it must be paired with a call to finalize.
termbox initialization errors.
Constructors
| FailedToOpenTTY | |
| PipeTrapError | |
| UnsupportedTerminal |
Instances
| Exception InitError Source # | |
Defined in Termbox.Internal.Main 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 | 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.1.0.2-AaPmFFv00o7Ls3oVRfNTsE" '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 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.
Constructors
| Mouse | |
Fields
| |
Instances
| Generic Mouse Source # | |
| Show Mouse Source # | |
| Eq Mouse Source # | |
| Ord Mouse Source # | |
| type Rep Mouse Source # | |
Defined in Termbox.Internal.Mouse type Rep Mouse = D1 ('MetaData "Mouse" "Termbox.Internal.Mouse" "termbox-1.1.0.2-AaPmFFv00o7Ls3oVRfNTsE" 'False) (C1 ('MetaCons "Mouse" 'PrefixI 'True) (S1 ('MetaSel ('Just "button") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseButton) :*: S1 ('MetaSel ('Just "pos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos))) | |
data MouseButton where Source #
A mouse button.
Bundled Patterns
| pattern LeftClick :: MouseButton | |
| pattern MiddleClick :: MouseButton | |
| pattern ReleaseClick :: MouseButton | |
| pattern RightClick :: MouseButton | |
| pattern WheelDown :: MouseButton | |
| pattern WheelUp :: MouseButton |
Instances
| Show MouseButton Source # | |
Defined in Termbox.Internal.Mouse Methods showsPrec :: Int -> MouseButton -> ShowS # show :: MouseButton -> String # showList :: [MouseButton] -> ShowS # | |
| Eq MouseButton Source # | |
Defined in Termbox.Internal.Mouse | |
| Ord MouseButton Source # | |
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 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.1.0.2-AaPmFFv00o7Ls3oVRfNTsE" '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.1.0.2-AaPmFFv00o7Ls3oVRfNTsE" 'False) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "width") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))) | |