termbox-0.2.0: termbox bindings

Safe HaskellNone
LanguageHaskell2010

Termbox

Contents

Description

A termbox program is typically constructed as an infinite loop that:

  1. clears the terminal backbuffer.
  2. Renders the program state by setting individual pixels.
  3. flushes the backbuffer to the terminal.
  4. polls for an event to update the program state.

For example, this progam simply displays the number of keys pressed, and quits on Esc:

{-# LANGUAGE LambdaCase #-}

import Data.Foldable (for_)
import qualified Termbox

main :: IO ()
main =
  Termbox.run_ (loop 0)

loop :: Int -> IO ()
loop n = do
  Termbox.clear mempty mempty
  render n
  Termbox.flush

  Termbox.poll >>= \case
    Termbox.EventKey Termbox.KeyEsc _ ->
      pure ()
    _ ->
      loop (n+1)

render :: Int -> IO ()
render n =
  for_
    (zip [0..] (show n))
    (\(i, c) ->
      Termbox.set i 0 (Termbox.Cell c mempty mempty))

Other termbox features include cell attributes (style, color), cursor display, and mouse click handling.

This module is intended to be imported qualified.

Synopsis

Initialization

run :: IO a -> IO (Either InitError a) Source #

Run a termbox program and restore the terminal state afterwards.

run_ :: IO a -> IO a Source #

Like run, but throws InitErrors as IO exceptions.

data InitError Source #

Termbox initialization errors that can be returned by run.

Terminal contents

set :: Int -> Int -> Cell -> IO () Source #

Set the cell at the given coordinates (column, then row).

getCells :: IO (Array (Int, Int) Cell) Source #

Get the terminal's two-dimensional array of cells (indexed by row, then column).

clear :: Attr -> Attr -> IO () Source #

Clear the back buffer with the given foreground and background attributes.

flush :: IO () Source #

Synchronize the internal back buffer with the terminal.

data Cell Source #

A Cell contains a character, foreground attribute, and background attribute.

Constructors

Cell !Char !Attr !Attr 
Instances
Eq Cell Source # 
Instance details

Defined in Termbox

Methods

(==) :: Cell -> Cell -> Bool #

(/=) :: Cell -> Cell -> Bool #

Show Cell Source # 
Instance details

Defined in Termbox

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Storable Cell Source # 
Instance details

Defined in Termbox

Methods

sizeOf :: Cell -> Int #

alignment :: Cell -> Int #

peekElemOff :: Ptr Cell -> Int -> IO Cell #

pokeElemOff :: Ptr Cell -> Int -> Cell -> IO () #

peekByteOff :: Ptr b -> Int -> IO Cell #

pokeByteOff :: Ptr b -> Int -> Cell -> IO () #

peek :: Ptr Cell -> IO Cell #

poke :: Ptr Cell -> Cell -> IO () #

Terminal size

getSize :: IO (Int, Int) Source #

Get the terminal size (width, then height).

Cursor manipulation

setCursor :: Int -> Int -> IO () Source #

Set the cursor coordinates (column, then row).

hideCursor :: IO () Source #

Hide the cursor.

Event handling

poll :: IO Event Source #

Block until an Event arrives.

Note: termbox v1.1.2 does not properly handle OS signals that interrupt the underlying select system call, so unfortunately the familiar Ctrl-C will not be able to stop a program stuck in pollEvent.

You can work around this issue by polling in a background thread using the threaded runtime, or simply writing event-handling code that is responsive to intuitive "quit" keys like q and Esc.

Throws: PollError

data Event Source #

A input event.

Constructors

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)

Instances
Eq Event Source # 
Instance details

Defined in Termbox

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Show Event Source # 
Instance details

Defined in Termbox

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

data Mouse Source #

A mouse event.

Instances
Eq Mouse Source # 
Instance details

Defined in Termbox

Methods

(==) :: Mouse -> Mouse -> Bool #

(/=) :: Mouse -> Mouse -> Bool #

Ord Mouse Source # 
Instance details

Defined in Termbox

Methods

compare :: Mouse -> Mouse -> Ordering #

(<) :: Mouse -> Mouse -> Bool #

(<=) :: Mouse -> Mouse -> Bool #

(>) :: Mouse -> Mouse -> Bool #

(>=) :: Mouse -> Mouse -> Bool #

max :: Mouse -> Mouse -> Mouse #

min :: Mouse -> Mouse -> Mouse #

Show Mouse Source # 
Instance details

Defined in Termbox

Methods

showsPrec :: Int -> Mouse -> ShowS #

show :: Mouse -> String #

showList :: [Mouse] -> ShowS #

data PollError Source #

An error occurred when polling, due to mysterious circumstances that are not well-documented in the original C codebase.

Constructors

PollError 

Attributes

black :: Attr Source #

black = 1.

red :: Attr Source #

red = 2.

green :: Attr Source #

green = 3.

yellow :: Attr Source #

yellow = 4.

blue :: Attr Source #

blue = 5.

magenta :: Attr Source #

magenta = 6.

cyan :: Attr Source #

cyan = 7.

white :: Attr Source #

white = 8.

bold :: Attr Source #

Bold modifier attribute.

underline :: Attr Source #

Underline modifier attribute.

reverse :: Attr Source #

Reverse modifier attribute.

data Attr Source #

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 Attrs this way, with a right bias.

Instances
Eq Attr Source # 
Instance details

Defined in Termbox

Methods

(==) :: Attr -> Attr -> Bool #

(/=) :: Attr -> Attr -> Bool #

Num Attr Source #

Provided for numeric literals.

Instance details

Defined in Termbox

Methods

(+) :: Attr -> Attr -> Attr #

(-) :: Attr -> Attr -> Attr #

(*) :: Attr -> Attr -> Attr #

negate :: Attr -> Attr #

abs :: Attr -> Attr #

signum :: Attr -> Attr #

fromInteger :: Integer -> Attr #

Semigroup Attr Source #

Left-biased color; attributes are merged.

Instance details

Defined in Termbox

Methods

(<>) :: Attr -> Attr -> Attr #

sconcat :: NonEmpty Attr -> Attr #

stimes :: Integral b => b -> Attr -> Attr #

Monoid Attr Source # 
Instance details

Defined in Termbox

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

Terminal modes

getInputMode :: HasCallStack => IO InputMode Source #

Get the current input mode.

setInputMode :: InputMode -> IO () Source #

Set the input mode.

data InputMode Source #

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.
Instances
Eq InputMode Source # 
Instance details

Defined in Termbox

Ord InputMode Source # 
Instance details

Defined in Termbox

Show InputMode Source # 
Instance details

Defined in Termbox

data MouseMode Source #

The mouse mode.

  • No. Don't handle mouse events.
  • Yes. Handle mouse events.

Constructors

MouseModeNo

Default.

MouseModeYes 
Instances
Eq MouseMode Source # 
Instance details

Defined in Termbox

Ord MouseMode Source # 
Instance details

Defined in Termbox

Show MouseMode Source # 
Instance details

Defined in Termbox

getOutputMode :: HasCallStack => IO OutputMode Source #

Get the current output mode.

setOutputMode :: OutputMode -> IO () Source #

Set the output mode.

data OutputMode Source #

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.