Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type TermboxEvent = Event
- run :: InputMode -> OutputMode -> (Event TermboxEvent -> Behavior (Int, Int) -> MomentIO (Behavior Scene, Event a)) -> IO (Either InitError a)
- run_ :: InputMode -> OutputMode -> (Event TermboxEvent -> Behavior (Int, Int) -> MomentIO (Behavior Scene, Event a)) -> IO a
- set :: Int -> Int -> Cell -> Cells
- data Scene = Scene !Cells !Cursor
- data Cells
- data Cursor
- black :: Attr
- red :: Attr
- green :: Attr
- yellow :: Attr
- blue :: Attr
- magenta :: Attr
- cyan :: Attr
- white :: Attr
- bold :: Attr
- underline :: Attr
- reverse :: Attr
- data Attr
- data Cell = Cell !Char !Attr !Attr
- data Event
- = EventKey !Key !Bool
- | EventResize !Int !Int
- | EventMouse !Mouse !Int !Int
- data InitError
- data InputMode
- 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 MouseMode
- data OutputMode
Documentation
See the bottom of this module for a simple, runnable example to get started.
Here's how to run the examples with cabal
:
cabal v2-run --constraint "termbox-banana +build-examples" termbox-banana-example-echo cabal v2-run --constraint "termbox-banana +build-examples" termbox-banana-example-hoogle
This module is intended to be imported qualified.
import qualified Termbox.Banana as Termbox
type TermboxEvent = Event Source #
A termbox
event. This type alias exists only for Haddock readability;
in code, you are encouraged to use
Event
forreactive-banana
eventsTermbox.Event
fortermbox
events
Since: 0.1.0
:: InputMode | |
-> OutputMode | |
-> (Event TermboxEvent -> Behavior (Int, Int) -> MomentIO (Behavior Scene, Event a)) | |
-> IO (Either InitError a) |
Run a termbox
program with the specified input and output modes.
Given
- the terminal event stream
- the time-varying terminal size (width, then height)
return
- a time-varying scene to render
- an event stream of arbitrary values, only the first of which is relevant,
which ends the
termbox
program and returns from themain
action.
Since: 0.2.0
set :: Int -> Int -> Cell -> Cells Source #
Set a single cell's value (column, then row).
Since: 0.1.0
Re-exports
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.
A Cell
contains a character, foreground attribute, and background
attribute.
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) |
Termbox initialization errors that can be returned by run
.
Instances
Show InitError | |
Exception InitError | |
Defined in Termbox toException :: InitError -> SomeException # fromException :: SomeException -> Maybe InitError # displayException :: InitError -> String # |
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.
A key event.
The mouse mode.
- No. Don't handle mouse events.
- Yes. Handle mouse events.
MouseModeNo | Default. |
MouseModeYes |
data OutputMode #
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 | |
Defined in Termbox (==) :: OutputMode -> OutputMode -> Bool # (/=) :: OutputMode -> OutputMode -> Bool # | |
Ord OutputMode | |
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 | |
Defined in Termbox showsPrec :: Int -> OutputMode -> ShowS # show :: OutputMode -> String # showList :: [OutputMode] -> ShowS # |
Example
Below is a sample program that simply displays the last key pressed, and
quits on Esc
:
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} module Main where import Reactive.Banana import Reactive.Banana.Frameworks import qualified Termbox.Banana as Termbox main :: IO () main = Termbox.run_
(Termbox.InputModeEsc
Termbox.MouseModeNo
) Termbox.OutputModeNormal
moment moment :: Event Termbox.Event
-> Behavior (Int, Int) -> MomentIO (Behavior Termbox.Scene
, Event ()) moment eEvent _bSize = do let eQuit :: Event () eQuit = () <$ filterE isKeyEsc eEvent bLatestEvent :: Behavior (Maybe Termbox.Event
) <- stepper Nothing (Just <$> eEvent) let bCells :: Behavior Termbox.Cells
bCells = maybe mempty renderEvent <$> bLatestEvent let bScene :: Behavior Termbox.Scene
bScene = Termbox.Scene
<$> bCells <*> pure Termbox.NoCursor
pure (bScene, eQuit) renderEvent :: Termbox.Event
-> Termbox.Cells
renderEvent = foldMap ((i, c) -> Termbox.set i 0 (Termbox.Cell
c mempty mempty)) . zip [0..] . show isKeyEsc :: Termbox.Event
-> Bool isKeyEsc = case Termbox.EventKey
Termbox.KeyEsc
_ -> True _ -> False