termbox-tea-1.0.0: termbox + The Elm Architecture
Safe HaskellSafe-Inferred
LanguageHaskell2010

Termbox.Tea

Description

This module provides an Elm Architecture interface to termbox, a simple C library for writing text-based user interfaces: https://github.com/termbox/termbox

See also:

👉 Quick start example

Expand

This termbox program displays the number of keys pressed.

{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedRecordDot #-}

import Data.Foldable (fold)
import Data.Function ((&))
import Data.Void (Void)
import Termbox.Tea qualified as Termbox

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

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

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

string :: [Char] -> Termbox.Image
string chars =
  zip [0 ..] chars & foldMap \(i, char) ->
    Termbox.char char & Termbox.atCol i
Synopsis

Main

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.

run either:

  • Returns immediately with an InitError.
  • Returns the final state, once it's finished.

data InitError #

termbox initialization errors.

Terminal contents

Scene

data Scene #

A scene, which contains an image, an optional background fill color, and an optional cursor.

  • Create a scene with image.
  • Set a scene's background fill color with fill.
  • Set a scene's cursor position with cursor.

image :: Image -> Scene #

Create a scene from an image.

fill :: Color -> Scene -> Scene #

Set a scene's background fill color.

cursor :: Pos -> Scene -> Scene #

Set a scene's cursor position.

Image

data Image #

An image.

Instances

Instances details
Monoid Image 
Instance details

Defined in Termbox.Internal.Image

Methods

mempty :: Image #

mappend :: Image -> Image -> Image #

mconcat :: [Image] -> Image #

Semigroup Image 
Instance details

Defined in Termbox.Internal.Image

Methods

(<>) :: Image -> Image -> Image #

sconcat :: NonEmpty Image -> Image #

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

char :: Char -> Image #

Create an image from a character.

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

Color

fg :: Color -> Image -> Image #

Set the foreground color of an image.

bg :: Color -> Image -> Image #

Set the background color of an image.

Style

bold :: Image -> Image #

Make an image bold.

underline :: Image -> Image #

Make an image underlined.

blink :: Image -> Image #

Make an image blink.

Translation

at :: Pos -> Image -> Image #

Translate an image.

atRow :: Int -> Image -> Image #

Translate an image by a number of rows.

atCol :: Int -> Image -> Image #

Translate an image by a number of columns.

Colors

data Color #

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

Instances

Instances details
Eq Color 
Instance details

Defined in Termbox.Internal.Color

Methods

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

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

Basic colors

bright :: Color -> Color #

Make a basic color bright.

216 miscellaneous colors

color :: Int -> Color #

A miscellaneous color.

Valid values are in the range [0, 215]; values outside of this range are clamped.

24 monochrome colors

gray :: Int -> Color #

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 #

An input event.

Constructors

EventKey !Key

Key event

EventResize !Size

Resize event

EventMouse !Mouse

Mouse event

EventUser !e

User event

Instances

Instances details
Generic (Event e) 
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) 
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) 
Instance details

Defined in Termbox.Internal.Event

Methods

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

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

type Rep (Event e) 
Instance details

Defined in Termbox.Internal.Event

data Key #

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 KeyCtrlUnderscore :: Key 
pattern KeyCtrlI :: Key 
pattern KeyCtrlM :: Key 
pattern KeyCtrl7 :: Key 
pattern KeyCtrl5 :: Key 
pattern KeyCtrl4 :: Key 
pattern KeyCtrl3 :: Key 
pattern KeyCtrl2 :: Key 
pattern KeyCtrlLsqBracket :: Key 
pattern KeyCtrlH :: Key 

Instances

Instances details
Show Key 
Instance details

Defined in Termbox.Internal.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Eq Key 
Instance details

Defined in Termbox.Internal.Key

Methods

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

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

Ord Key 
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 #

A mouse event.

Constructors

Mouse 

Fields

Instances

Instances details
Generic Mouse 
Instance details

Defined in Termbox.Internal.Mouse

Associated Types

type Rep Mouse :: Type -> Type #

Methods

from :: Mouse -> Rep Mouse x #

to :: Rep Mouse x -> Mouse #

Show Mouse 
Instance details

Defined in Termbox.Internal.Mouse

Methods

showsPrec :: Int -> Mouse -> ShowS #

show :: Mouse -> String #

showList :: [Mouse] -> ShowS #

Eq Mouse 
Instance details

Defined in Termbox.Internal.Mouse

Methods

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

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

Ord Mouse 
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 #

type Rep Mouse 
Instance details

Defined in Termbox.Internal.Mouse

type Rep Mouse = D1 ('MetaData "Mouse" "Termbox.Internal.Mouse" "termbox-2.0.0-inplace" 'False) (C1 ('MetaCons "Mouse" 'PrefixI 'True) (S1 ('MetaSel ('Just "button") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 MouseButton) :*: S1 ('MetaSel ('Just "pos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pos)))

data MouseButton where #

A mouse button.

Bundled Patterns

pattern WheelUp :: MouseButton 
pattern WheelDown :: MouseButton 
pattern ReleaseClick :: MouseButton 
pattern RightClick :: MouseButton 
pattern MiddleClick :: MouseButton 
pattern LeftClick :: MouseButton 

Miscellaneous types

data Pos #

A relative terminal position.

Constructors

Pos 

Fields

Instances

Instances details
Monoid Pos 
Instance details

Defined in Termbox.Internal.Pos

Methods

mempty :: Pos #

mappend :: Pos -> Pos -> Pos #

mconcat :: [Pos] -> Pos #

Semigroup Pos 
Instance details

Defined in Termbox.Internal.Pos

Methods

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

sconcat :: NonEmpty Pos -> Pos #

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

Generic Pos 
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 
Instance details

Defined in Termbox.Internal.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Eq Pos 
Instance details

Defined in Termbox.Internal.Pos

Methods

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

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

Ord Pos 
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 
Instance details

Defined in Termbox.Internal.Pos

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

posUp :: Int -> Pos -> Pos #

Move a position up.

posDown :: Int -> Pos -> Pos #

Move a position down.

posLeft :: Int -> Pos -> Pos #

Move a position left.

posRight :: Int -> Pos -> Pos #

Move a position right.

data Size #

A terminal size.

Constructors

Size 

Fields

Instances

Instances details
Generic Size 
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 
Instance details

Defined in Termbox.Internal.Size

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Eq Size 
Instance details

Defined in Termbox.Internal.Size

Methods

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

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

Ord Size 
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 
Instance details

Defined in Termbox.Internal.Size

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