termbox-banana-0.3.0: reactive-banana + termbox
Safe HaskellSafe-Inferred
LanguageHaskell2010

Termbox.Banana

Synopsis

Introduction

This module is intended to be imported qualified:

import qualified Termbox.Banana as Termbox

👉 Quick start example

Expand

This is a program that displays the last key pressed, and quits on Esc:

{-# LANGUAGE LambdaCase          #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import Reactive.Banana
import Reactive.Banana.Frameworks

import qualified Termbox.Banana as Termbox

main :: IO ()
main =
  Termbox.run moment

moment
  :: Event Termbox.Event
  -> Behavior (Int, Int)
  -> MomentIO (Behavior (Termbox.Cells, Termbox.Cursor), Event ())
moment eEvent _bSize = do
  let
    eQuit :: Event ()
    eQuit =
      () <$ filterE isKeyEsc eEvent

  bLatestEvent :: Behavior (Maybe Termbox.Event) <-
    stepper
      Nothing
      (Just <$> eEvent)

  let
    bCells :: Behavior Termbox.Cells
    bCells =
      maybe mempty renderEvent <$> bLatestEvent

  let
    bScene :: Behavior (Termbox.Cells, Termbox.Cursor)
    bScene =
      (,)
        <$> bCells
        <*> pure Termbox.NoCursor

  pure (bScene, eQuit)

renderEvent :: Termbox.Event -> Termbox.Cells
renderEvent =
  foldMap (\(i, c) -> Termbox.set i 0 (Termbox.Cell c mempty mempty))
    . zip [0..]
    . show

isKeyEsc :: Termbox.Event -> Bool
isKeyEsc = \case
  Termbox.EventKey Termbox.KeyEsc -> True
  _ -> False

Core API

type TermboxEvent = Event Source #

A termbox event. This type alias exists only for Haddock readability; in code, you are encouraged to use

  • Event for reactive-banana events
  • Termbox.Event for termbox events

run :: (Event TermboxEvent -> Behavior (Int, Int) -> MomentIO (Behavior (Cells, Cursor), Event a)) -> IO a Source #

Run a termbox program with the specified input and output modes.

Given

  • the terminal event stream
  • the time-varying terminal size (width, then height)

return

  • a time-varying scene to render
  • an event stream of arbitrary values, only the first of which is relevant, which ends the termbox program and returns from the main action.

Re-exports from termbox

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

data Attr #

Instances

Instances details
Monoid Attr 
Instance details

Defined in Termbox.Attr

Methods

mempty :: Attr #

mappend :: Attr -> Attr -> Attr #

mconcat :: [Attr] -> Attr #

Semigroup Attr 
Instance details

Defined in Termbox.Attr

Methods

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

sconcat :: NonEmpty Attr -> Attr #

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

Num Attr 
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 
Instance details

Defined in Termbox.Attr

Methods

showsPrec :: Int -> Attr -> ShowS #

show :: Attr -> String #

showList :: [Attr] -> ShowS #

Eq Attr 
Instance details

Defined in Termbox.Attr

Methods

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

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

data Cell #

Constructors

Cell !Char !Attr !Attr 

Instances

Instances details
Storable Cell 
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 () #

Show Cell 
Instance details

Defined in Termbox.Cell

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Eq Cell 
Instance details

Defined in Termbox.Cell

Methods

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

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

data Cells #

Instances

Instances details
Monoid Cells 
Instance details

Defined in Termbox.Cells

Methods

mempty :: Cells #

mappend :: Cells -> Cells -> Cells #

mconcat :: [Cells] -> Cells #

Semigroup Cells 
Instance details

Defined in Termbox.Cells

Methods

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

sconcat :: NonEmpty Cells -> Cells #

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

data Cursor #

Constructors

Cursor !Int !Int 
NoCursor 

data Event #

Instances

Instances details
Show Event 
Instance details

Defined in Termbox.Event

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event 
Instance details

Defined in Termbox.Event

Methods

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

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

data InitError #

Instances

Instances details
Exception InitError 
Instance details

Defined in Termbox

Show InitError 
Instance details

Defined in Termbox

pattern KeyCtrl2 :: Key #

pattern KeyCtrl3 :: Key #

pattern KeyCtrl4 :: Key #

pattern KeyCtrl5 :: Key #

pattern KeyCtrl7 :: Key #

pattern KeyCtrlH :: Key #

pattern KeyCtrlI :: Key #

pattern KeyCtrlM :: Key #

data Mouse #

Instances

Instances details
Show Mouse 
Instance details

Defined in Termbox.Mouse

Methods

showsPrec :: Int -> Mouse -> ShowS #

show :: Mouse -> String #

showList :: [Mouse] -> ShowS #

Eq Mouse 
Instance details

Defined in Termbox.Mouse

Methods

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

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

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

data PollError #

Constructors

PollError 

Instances

Instances details
Exception PollError 
Instance details

Defined in Termbox.Event

Show PollError 
Instance details

Defined in Termbox.Event