Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides a low-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:
termbox
, a higher-level interface.termbox-banana
, areactive-banana
FRP interface.termbox-tea
, an Elm Architecture interface.
Synopsis
- tb_init :: IO (Either Tb_init_error ())
- tb_init_fd :: Fd -> IO (Either Tb_init_error ())
- tb_init_file :: FilePath -> IO (Either Tb_init_error ())
- tb_shutdown :: IO ()
- tb_get_input_mode :: IO Tb_input_mode
- tb_select_input_mode :: Tb_input_mode -> IO ()
- tb_get_output_mode :: IO Tb_output_mode
- tb_select_output_mode :: Tb_output_mode -> IO ()
- tb_width :: IO Int
- tb_height :: IO Int
- tb_peek_event :: Int -> IO (Either () (Maybe Tb_event))
- tb_poll_event :: IO (Either () Tb_event)
- tb_set_cursor :: Maybe (Int, Int) -> IO ()
- tb_put_cell :: Int -> Int -> Tb_cell -> IO ()
- tb_change_cell :: Int -> Int -> Char -> Tb_attrs -> Tb_attrs -> IO ()
- tb_clear :: IO ()
- tb_set_clear_attributes :: Tb_attrs -> Tb_attrs -> IO ()
- tb_present :: IO ()
- data Tb_cell = Tb_cell {}
- newtype Tb_attrs = Tb_attrs Word16
- _TB_DEFAULT :: Tb_attrs
- _TB_BLACK :: Tb_attrs
- _TB_BLUE :: Tb_attrs
- _TB_CYAN :: Tb_attrs
- _TB_GREEN :: Tb_attrs
- _TB_MAGENTA :: Tb_attrs
- _TB_RED :: Tb_attrs
- _TB_WHITE :: Tb_attrs
- _TB_YELLOW :: Tb_attrs
- _TB_BOLD :: Tb_attrs
- _TB_REVERSE :: Tb_attrs
- _TB_UNDERLINE :: Tb_attrs
- data Tb_event = Tb_event {}
- data Tb_event_mod where
- pattern TB_MOD_ALT :: Tb_event_mod
- pattern TB_MOD_MOTION :: Tb_event_mod
- data Tb_event_type where
- pattern TB_EVENT_KEY :: Tb_event_type
- pattern TB_EVENT_MOUSE :: Tb_event_type
- pattern TB_EVENT_RESIZE :: Tb_event_type
- data Tb_init_error where
- pattern TB_EFAILED_TO_OPEN_TTY :: Tb_init_error
- pattern TB_EPIPE_TRAP_ERROR :: Tb_init_error
- pattern TB_EUNSUPPORTED_TERMINAL :: Tb_init_error
- newtype Tb_input_mode = Tb_input_mode CInt
- _TB_INPUT_ALT :: Tb_input_mode
- _TB_INPUT_ESC :: Tb_input_mode
- _TB_INPUT_MOUSE :: Tb_input_mode
- data Tb_key where
- pattern TB_KEY_ARROW_DOWN :: Tb_key
- pattern TB_KEY_ARROW_LEFT :: Tb_key
- pattern TB_KEY_ARROW_RIGHT :: Tb_key
- pattern TB_KEY_ARROW_UP :: Tb_key
- pattern TB_KEY_BACKSPACE :: Tb_key
- pattern TB_KEY_BACKSPACE2 :: Tb_key
- pattern TB_KEY_CTRL_2 :: Tb_key
- pattern TB_KEY_CTRL_3 :: Tb_key
- pattern TB_KEY_CTRL_4 :: Tb_key
- pattern TB_KEY_CTRL_5 :: Tb_key
- pattern TB_KEY_CTRL_6 :: Tb_key
- pattern TB_KEY_CTRL_7 :: Tb_key
- pattern TB_KEY_CTRL_8 :: Tb_key
- pattern TB_KEY_CTRL_A :: Tb_key
- pattern TB_KEY_CTRL_B :: Tb_key
- pattern TB_KEY_CTRL_BACKSLASH :: Tb_key
- pattern TB_KEY_CTRL_C :: Tb_key
- pattern TB_KEY_CTRL_D :: Tb_key
- pattern TB_KEY_CTRL_E :: Tb_key
- pattern TB_KEY_CTRL_F :: Tb_key
- pattern TB_KEY_CTRL_G :: Tb_key
- pattern TB_KEY_CTRL_H :: Tb_key
- pattern TB_KEY_CTRL_I :: Tb_key
- pattern TB_KEY_CTRL_J :: Tb_key
- pattern TB_KEY_CTRL_K :: Tb_key
- pattern TB_KEY_CTRL_L :: Tb_key
- pattern TB_KEY_CTRL_LSQ_BRACKET :: Tb_key
- pattern TB_KEY_CTRL_M :: Tb_key
- pattern TB_KEY_CTRL_N :: Tb_key
- pattern TB_KEY_CTRL_O :: Tb_key
- pattern TB_KEY_CTRL_P :: Tb_key
- pattern TB_KEY_CTRL_Q :: Tb_key
- pattern TB_KEY_CTRL_R :: Tb_key
- pattern TB_KEY_CTRL_RSQ_BRACKET :: Tb_key
- pattern TB_KEY_CTRL_S :: Tb_key
- pattern TB_KEY_CTRL_SLASH :: Tb_key
- pattern TB_KEY_CTRL_T :: Tb_key
- pattern TB_KEY_CTRL_TILDE :: Tb_key
- pattern TB_KEY_CTRL_U :: Tb_key
- pattern TB_KEY_CTRL_UNDERSCORE :: Tb_key
- pattern TB_KEY_CTRL_V :: Tb_key
- pattern TB_KEY_CTRL_W :: Tb_key
- pattern TB_KEY_CTRL_X :: Tb_key
- pattern TB_KEY_CTRL_Y :: Tb_key
- pattern TB_KEY_CTRL_Z :: Tb_key
- pattern TB_KEY_DELETE :: Tb_key
- pattern TB_KEY_END :: Tb_key
- pattern TB_KEY_ENTER :: Tb_key
- pattern TB_KEY_ESC :: Tb_key
- pattern TB_KEY_F1 :: Tb_key
- pattern TB_KEY_F10 :: Tb_key
- pattern TB_KEY_F11 :: Tb_key
- pattern TB_KEY_F12 :: Tb_key
- pattern TB_KEY_F2 :: Tb_key
- pattern TB_KEY_F3 :: Tb_key
- pattern TB_KEY_F4 :: Tb_key
- pattern TB_KEY_F5 :: Tb_key
- pattern TB_KEY_F6 :: Tb_key
- pattern TB_KEY_F7 :: Tb_key
- pattern TB_KEY_F8 :: Tb_key
- pattern TB_KEY_F9 :: Tb_key
- pattern TB_KEY_HOME :: Tb_key
- pattern TB_KEY_INSERT :: Tb_key
- pattern TB_KEY_MOUSE_LEFT :: Tb_key
- pattern TB_KEY_MOUSE_MIDDLE :: Tb_key
- pattern TB_KEY_MOUSE_RELEASE :: Tb_key
- pattern TB_KEY_MOUSE_RIGHT :: Tb_key
- pattern TB_KEY_MOUSE_WHEEL_DOWN :: Tb_key
- pattern TB_KEY_MOUSE_WHEEL_UP :: Tb_key
- pattern TB_KEY_PGDN :: Tb_key
- pattern TB_KEY_PGUP :: Tb_key
- pattern TB_KEY_SPACE :: Tb_key
- pattern TB_KEY_TAB :: Tb_key
- data Tb_output_mode where
- pattern TB_OUTPUT_216 :: Tb_output_mode
- pattern TB_OUTPUT_256 :: Tb_output_mode
- pattern TB_OUTPUT_GRAYSCALE :: Tb_output_mode
- pattern TB_OUTPUT_NORMAL :: Tb_output_mode
Functions
Initialize / shutdown
tb_init_fd :: Fd -> IO (Either Tb_init_error ()) Source #
Initialize the termbox
library.
tb_init = tb_init_fd(0)
tb_init_file :: FilePath -> IO (Either Tb_init_error ()) Source #
Initialize the termbox
library.
tb_init = tb_init_file("/dev/tty")
tb_shutdown :: IO () #
Shutdown the termbox
library.
Get or set input mode
tb_get_input_mode :: IO Tb_input_mode Source #
Get the input mode.
tb_select_input_mode :: Tb_input_mode -> IO () Source #
Set the input mode.
Get or set output mode
tb_get_output_mode :: IO Tb_output_mode Source #
Get the output mode.
tb_select_output_mode :: Tb_output_mode -> IO () Source #
Set the output mode.
Get terminal dimensions
Poll for events
tb_peek_event :: Int -> IO (Either () (Maybe Tb_event)) Source #
Wait up to a number of milliseconds for an event.
Set a cell
Set a cell value in the back buffer.
Clear and synchronize the back buffer
tb_set_clear_attributes Source #
Set the foreground and background attributes that tb_clear
clears the back buffer with.
tb_present :: IO () #
Synchronize the back buffer with the terminal.
Types
A cell.
Instances
Generic Tb_cell Source # | |
Show Tb_cell Source # | |
Eq Tb_cell Source # | |
type Rep Tb_cell Source # | |
Defined in Termbox.Bindings.Hs.Internal.Cell type Rep Tb_cell = D1 ('MetaData "Tb_cell" "Termbox.Bindings.Hs.Internal.Cell" "termbox-bindings-hs-1.0.0-inplace" 'False) (C1 ('MetaCons "Tb_cell" 'PrefixI 'True) (S1 ('MetaSel ('Just "ch") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Char) :*: (S1 ('MetaSel ('Just "fg") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Tb_attrs) :*: S1 ('MetaSel ('Just "bg") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Tb_attrs)))) |
Cell attributes.
An event.
Instances
data Tb_event_mod where Source #
An event modifier.
pattern TB_MOD_ALT :: Tb_event_mod | |
pattern TB_MOD_MOTION :: Tb_event_mod |
Instances
Show Tb_event_mod Source # | |
Defined in Termbox.Bindings.Hs.Internal.EventMod showsPrec :: Int -> Tb_event_mod -> ShowS # show :: Tb_event_mod -> String # showList :: [Tb_event_mod] -> ShowS # | |
Eq Tb_event_mod Source # | |
Defined in Termbox.Bindings.Hs.Internal.EventMod (==) :: Tb_event_mod -> Tb_event_mod -> Bool # (/=) :: Tb_event_mod -> Tb_event_mod -> Bool # |
data Tb_event_type where Source #
An event type.
pattern TB_EVENT_KEY :: Tb_event_type | |
pattern TB_EVENT_MOUSE :: Tb_event_type | |
pattern TB_EVENT_RESIZE :: Tb_event_type |
Instances
Show Tb_event_type Source # | |
Defined in Termbox.Bindings.Hs.Internal.EventType showsPrec :: Int -> Tb_event_type -> ShowS # show :: Tb_event_type -> String # showList :: [Tb_event_type] -> ShowS # | |
Eq Tb_event_type Source # | |
Defined in Termbox.Bindings.Hs.Internal.EventType (==) :: Tb_event_type -> Tb_event_type -> Bool # (/=) :: Tb_event_type -> Tb_event_type -> Bool # |
data Tb_init_error where Source #
A tb_init
error.
pattern TB_EFAILED_TO_OPEN_TTY :: Tb_init_error | |
pattern TB_EPIPE_TRAP_ERROR :: Tb_init_error | |
pattern TB_EUNSUPPORTED_TERMINAL :: Tb_init_error |
Instances
Exception Tb_init_error Source # | |
Defined in Termbox.Bindings.Hs.Internal.InitError | |
Show Tb_init_error Source # | |
Defined in Termbox.Bindings.Hs.Internal.InitError showsPrec :: Int -> Tb_init_error -> ShowS # show :: Tb_init_error -> String # showList :: [Tb_init_error] -> ShowS # | |
Eq Tb_init_error Source # | |
Defined in Termbox.Bindings.Hs.Internal.InitError (==) :: Tb_init_error -> Tb_init_error -> Bool # (/=) :: Tb_init_error -> Tb_init_error -> Bool # |
newtype Tb_input_mode Source #
The input mode.
Instances
A key.
data Tb_output_mode where Source #
The output mode.
pattern TB_OUTPUT_216 :: Tb_output_mode | |
pattern TB_OUTPUT_256 :: Tb_output_mode | |
pattern TB_OUTPUT_GRAYSCALE :: Tb_output_mode | |
pattern TB_OUTPUT_NORMAL :: Tb_output_mode |
Instances
Show Tb_output_mode Source # | |
Defined in Termbox.Bindings.Hs.Internal.OutputMode showsPrec :: Int -> Tb_output_mode -> ShowS # show :: Tb_output_mode -> String # showList :: [Tb_output_mode] -> ShowS # | |
Eq Tb_output_mode Source # | |
Defined in Termbox.Bindings.Hs.Internal.OutputMode (==) :: Tb_output_mode -> Tb_output_mode -> Bool # (/=) :: Tb_output_mode -> Tb_output_mode -> Bool # |