termbox-1.0.0: termbox
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

This module is intended to be imported qualified.

👉 Quick start example

Expand

This termbox program displays the number of keys pressed.

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoFieldSelectors #-}

import Data.Foldable (fold)
import Data.Void (Void)
import Termbox qualified

main :: IO ()
main = do
  result <-
    Termbox.run
      Termbox.Program
        { initialize,
          pollEvent,
          handleEvent,
          handleEventError,
          render,
          finished
        }
  case result of
    Left err -> putStrLn ("Termbox program failed to initialize: " ++ show err)
    Right state -> putStrLn ("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

handleEventError :: MyState -> IO MyState
handleEventError state =
  pure state

render :: MyState -> Termbox.Scene
render state =
  fold
    [ string
        Termbox.Pos {row = 2, col = 4}
        ("Number of keys pressed: " ++ map Termbox.char (show state.keysPressed))
    , string
        Termbox.Pos {row = 4, col = 4}
        ("Press " ++ map (Termbox.bold . Termbox.char) Esc ++ " to quit.")
    ]

finished :: MyState -> Bool
finished state =
  state.pressedEsc

string :: Termbox.Pos -> [Termbox.Cell] -> Termbox.Scene
string pos cells =
  foldMap
    (\(i, cell) ->
      Termbox.cell
        Termbox.Pos {row = pos.row, col = pos.col + i}
        cell)
    (zip [0 ..] cells)
Synopsis

Termbox

data Program s Source #

A termbox program, parameterized by state s.

Constructors

forall e. Program 

Fields

run :: Program s -> IO (Either InitError s) Source #

Run a termbox program.

Either returns immediately with an InitError, or once the program state is finished with the final state.

data InitError Source #

termbox initialization errors.

Instances

Instances details
Exception InitError Source # 
Instance details

Defined in Termbox

Show InitError Source # 
Instance details

Defined in Termbox

Terminal contents

Scene

data Scene Source #

A scene.

  • Set individual cells with cell.
  • Set the background fill color with fill.
  • Set the cursor position with cursor.
  • Combine scenes together with <>.

Instances

Instances details
Monoid Scene Source # 
Instance details

Defined in Termbox.Internal.Scene

Methods

mempty :: Scene #

mappend :: Scene -> Scene -> Scene #

mconcat :: [Scene] -> Scene #

Semigroup Scene Source # 
Instance details

Defined in Termbox.Internal.Scene

Methods

(<>) :: Scene -> Scene -> Scene #

sconcat :: NonEmpty Scene -> Scene #

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

cell :: Pos -> Cell -> Scene Source #

Set a single cell.

fill :: Color -> Scene Source #

Set the background fill color.

cursor :: Pos -> Scene Source #

Set the cursor position.

Cell

data Cell Source #

A single cell.

Instances

Instances details
IsString [Cell] Source # 
Instance details

Defined in Termbox.Internal.Cell

Methods

fromString :: String -> [Cell] #

char :: Char -> Cell Source #

Create a cell from a character.

If the character is not 1 character wide, it will not be displayed.

fg :: Color -> Cell -> Cell Source #

Set the foreground color of a cell.

bg :: Color -> Cell -> Cell Source #

Set the background color of a cell.

bold :: Cell -> Cell Source #

Make a cell bold.

underline :: Cell -> Cell Source #

Make a cell underlined.

blink :: Cell -> Cell Source #

Make a cell blink.

Colors

data Color Source #

A color.

There are three classes of colors:

  • Basic named colors and their bright variants, such as red and bright blue.
  • Miscellaneous colors, such as color 33.
  • Monochrome colors that range from black (gray 0) to white (gray 23).

Basic colors

bright :: Color -> Color Source #

Make a basic color brighter.

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

gray :: Int -> Color Source #

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

data Event e Source #

An input event.

Constructors

EventKey !Key

Key event

EventResize !Size

Resize event

EventMouse !Mouse !Pos

Mouse event

EventUser !e

User event

Instances

Instances details
Generic (Event e) Source # 
Instance details

Defined in Termbox.Internal.Event

Associated Types

type Rep (Event e) :: Type -> Type #

Methods

from :: Event e -> Rep (Event e) x #

to :: Rep (Event e) x -> Event e #

Show e => Show (Event e) Source # 
Instance details

Defined in Termbox.Internal.Event

Methods

showsPrec :: Int -> Event e -> ShowS #

show :: Event e -> String #

showList :: [Event e] -> ShowS #

Eq e => Eq (Event e) Source # 
Instance details

Defined in Termbox.Internal.Event

Methods

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

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

type Rep (Event e) Source # 
Instance details

Defined in Termbox.Internal.Event

data Key Source #

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.

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 

Instances

Instances details
Show Key Source # 
Instance details

Defined in Termbox.Internal.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key Source # 
Instance details

Defined in Termbox.Internal.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in Termbox.Internal.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 #

data Mouse where Source #

A mouse event.

Bundled Patterns

pattern MouseLeft :: Mouse 
pattern MouseMiddle :: Mouse 
pattern MouseRelease :: Mouse 
pattern MouseRight :: Mouse 
pattern MouseWheelDown :: Mouse 
pattern MouseWheelUp :: Mouse 

Instances

Instances details
Show Mouse Source # 
Instance details

Defined in Termbox.Internal.Mouse

Methods

showsPrec :: Int -> Mouse -> ShowS #

show :: Mouse -> String #

showList :: [Mouse] -> ShowS #

Eq Mouse Source # 
Instance details

Defined in Termbox.Internal.Mouse

Methods

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

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

Ord Mouse Source # 
Instance details

Defined in Termbox.Internal.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 #

Miscellaneous types

data Pos Source #

A terminal position.

Constructors

Pos 

Fields

Instances

Instances details
Generic Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

Associated Types

type Rep Pos :: Type -> Type #

Methods

from :: Pos -> Rep Pos x #

to :: Rep Pos x -> Pos #

Show Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Eq Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

Methods

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

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

Ord Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

Methods

compare :: Pos -> Pos -> Ordering #

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

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

(>) :: Pos -> Pos -> Bool #

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

max :: Pos -> Pos -> Pos #

min :: Pos -> Pos -> Pos #

type Rep Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

type Rep Pos = D1 ('MetaData "Pos" "Termbox.Internal.Pos" "termbox-1.0.0-DPWGBoIlJyKFQWwmcVdGn9" 'False) (C1 ('MetaCons "Pos" 'PrefixI 'True) (S1 ('MetaSel ('Just "row") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "col") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))

posUp :: Int -> Pos -> Pos Source #

Move a position up.

posDown :: Int -> Pos -> Pos Source #

Move a position down.

posLeft :: Int -> Pos -> Pos Source #

Move a position left.

posRight :: Int -> Pos -> Pos Source #

Move a position right.

data Size Source #

A terminal size.

Constructors

Size 

Fields

Instances

Instances details
Generic Size Source # 
Instance details

Defined in Termbox.Internal.Size

Associated Types

type Rep Size :: Type -> Type #

Methods

from :: Size -> Rep Size x #

to :: Rep Size x -> Size #

Show Size Source # 
Instance details

Defined in Termbox.Internal.Size

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Eq Size Source # 
Instance details

Defined in Termbox.Internal.Size

Methods

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

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

Ord Size Source # 
Instance details

Defined in Termbox.Internal.Size

Methods

compare :: Size -> Size -> Ordering #

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

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

(>) :: Size -> Size -> Bool #

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

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

type Rep Size Source # 
Instance details

Defined in Termbox.Internal.Size

type Rep Size = D1 ('MetaData "Size" "Termbox.Internal.Size" "termbox-1.0.0-DPWGBoIlJyKFQWwmcVdGn9" 'False) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "width") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))