termbox-2.0.0.1: 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

You may prefer to use one of the following interfaces instead:

Synopsis

Main

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

Initialize a termbox program, and if that succeeds, run the provided action, then finalize the termbox program.

initialize :: IO (Either InitError ()) Source #

Initialize a termbox program.

If initialize succeeds, it must be paired with a call to finalize.

finalize :: IO () Source #

Shut down a termbox program.

data InitError Source #

termbox initialization errors.

Terminal contents

Scene

data Scene Source #

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 Source #

Create a scene from an image.

fill :: Color -> Scene -> Scene Source #

Set a scene's background fill color.

cursor :: Pos -> Scene -> Scene Source #

Set a scene's cursor position.

render :: Scene -> IO () Source #

Render a scene.

Image

data Image Source #

An image.

Instances

Instances details
Monoid Image Source # 
Instance details

Defined in Termbox.Internal.Image

Methods

mempty :: Image #

mappend :: Image -> Image -> Image #

mconcat :: [Image] -> Image #

Semigroup Image Source # 
Instance details

Defined in Termbox.Internal.Image

Methods

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

sconcat :: NonEmpty Image -> Image #

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

char :: Char -> Image Source #

Create an image from a character.

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

Color

fg :: Color -> Image -> Image Source #

Set the foreground color of an image.

bg :: Color -> Image -> Image Source #

Set the background color of an image.

Style

bold :: Image -> Image Source #

Make an image bold.

underline :: Image -> Image Source #

Make an image underlined.

blink :: Image -> Image Source #

Make an image blink.

Translation

at :: Pos -> Image -> Image Source #

Translate an image.

atRow :: Int -> Image -> Image Source #

Translate an image by a number of rows.

atCol :: Int -> Image -> Image Source #

Translate an image by a number of columns.

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

Instances

Instances details
Eq Color Source # 
Instance details

Defined in Termbox.Internal.Color

Methods

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

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

Basic colors

bright :: Color -> Color Source #

Make a basic color bright.

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

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 Source #

A mouse event.

Constructors

Mouse 

Fields

Instances

Instances details
Generic Mouse Source # 
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 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 #

type Rep Mouse Source # 
Instance details

Defined in Termbox.Internal.Mouse

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

poll :: IO (Event e) Source #

Poll for an event.

Miscellaneous types

data Pos Source #

A relative terminal position.

Constructors

Pos 

Fields

Instances

Instances details
Monoid Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

Methods

mempty :: Pos #

mappend :: Pos -> Pos -> Pos #

mconcat :: [Pos] -> Pos #

Semigroup Pos Source # 
Instance details

Defined in Termbox.Internal.Pos

Methods

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

sconcat :: NonEmpty Pos -> Pos #

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

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-2.0.0.1-inplace" '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-2.0.0.1-inplace" 'False) (C1 ('MetaCons "Size" 'PrefixI 'True) (S1 ('MetaSel ('Just "width") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))

getSize :: IO Size Source #

Get the current terminal size.