termbox-0.3.0: termbox bindings

Safe HaskellNone
LanguageHaskell2010

Termbox

Contents

Description

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

  1. Renders a scene.
  2. Polls for an event.

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

{-# LANGUAGE LambdaCase #-}

import qualified Termbox

main :: IO ()
main =
  Termbox.run (\_width _height render poll -> loop render poll 0)

loop :: (Termbox.Cells -> Termbox.Cursor -> IO ()) -> IO Termbox.Event -> Int -> IO ()
loop render poll n = do
  render (string (show n)) Termbox.NoCursor

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

string :: Int -> Int -> String -> Termbox.Cells
string col row =
  foldMap (\(i, c) -> Termbox.set (col + i) row (Termbox.Cell c 0 0)) . zip [0..]

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 :: (Int -> Int -> (Cells -> Cursor -> IO ()) -> IO Event -> IO a) -> IO a Source #

Run a termbox program and restore the terminal state afterwards.

The function provided to run is provided:

  • The initial terminal width
  • The initial terminal height
  • An action that renders a scene
  • An action that polls for an event indefinitely

Throws: InitError

data InitError Source #

Termbox initialization errors.

Terminal contents

set :: Int -> Int -> Cell -> Cells Source #

Set a single cell's value (column, then row).

data Cells Source #

A grid of cells. Create with set and combine with (<>).

Instances
Semigroup Cells Source # 
Instance details

Defined in Termbox.Cells

Methods

(<>) :: Cells -> Cells -> Cells #

sconcat :: NonEmpty Cells -> Cells #

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

Monoid Cells Source # 
Instance details

Defined in Termbox.Cells

Methods

mempty :: Cells #

mappend :: Cells -> Cells -> Cells #

mconcat :: [Cells] -> Cells #

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.Cell

Methods

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

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

Show Cell Source # 
Instance details

Defined in Termbox.Cell

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Storable Cell Source # 
Instance details

Defined in Termbox.Cell

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 () #

data Cursor Source #

A cursor.

Constructors

Cursor !Int !Int

Column, then row

NoCursor 

Event handling

data Event Source #

A input event.

Constructors

EventKey !Key

Key event

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.Event

Methods

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

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

Show Event Source # 
Instance details

Defined in Termbox.Event

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

data Key Source #

A key event.

Instances
Eq Key Source # 
Instance details

Defined in Termbox.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in Termbox.Key

Methods

compare :: Key -> Key -> Ordering #

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

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

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Termbox.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

In a few cases, distinct key sequences map to equivalent key events. The pattern synonyms below are provided for an alternate syntax in these cases, if desired.

pattern KeyCtrlH :: Key Source #

pattern KeyCtrl2 :: Key Source #

pattern KeyCtrl3 :: Key Source #

pattern KeyCtrl4 :: Key Source #

pattern KeyCtrl5 :: Key Source #

pattern KeyCtrl7 :: Key Source #

pattern KeyCtrlM :: Key Source #

pattern KeyCtrlI :: Key Source #

data Mouse Source #

A mouse event.

Instances
Eq Mouse Source # 
Instance details

Defined in Termbox.Mouse

Methods

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

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

Ord Mouse Source # 
Instance details

Defined in Termbox.Mouse

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.Mouse

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

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.Attr

Methods

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

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

Num Attr Source #

Provided for numeric literals.

Instance details

Defined in Termbox.Attr

Methods

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

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

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

negate :: Attr -> Attr #

abs :: Attr -> Attr #

signum :: Attr -> Attr #

fromInteger :: Integer -> Attr #

Show Attr Source # 
Instance details

Defined in Termbox.Attr

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Semigroup Attr Source #

Right-biased color; attributes are merged.

Instance details

Defined in Termbox.Attr

Methods

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

sconcat :: NonEmpty Attr -> Attr #

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

Monoid Attr Source # 
Instance details

Defined in Termbox.Attr

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

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.