{-# language InstanceSigs #-}
{-# language LambdaCase #-}
{-# language RankNTypes #-}
{-# language RecordWildCards #-}
{-# language ScopedTypeVariables #-}
{-# language TypeFamilies #-}
{-# language UnicodeSyntax #-}
module Termbox
(
main
, InitError(..)
, Cell(..)
, set
, buffer
, clear
, flush
, size
, setCursor
, hideCursor
, Event(..)
, Key(..)
, Mouse(..)
, poll
, PollError(..)
, Attr
, black
, red
, green
, yellow
, blue
, magenta
, cyan
, white
, bold
, underline
, reverse
, InputMode(..)
, MouseMode(..)
, getInputMode
, setInputMode
, OutputMode(..)
, getOutputMode
, setOutputMode
) where
import Prelude hiding (mod, reverse)
import qualified Termbox.Internal as Tb
import Control.Exception
import Control.Monad (join)
import Data.Array.Storable
import Data.Bits ((.|.), (.&.))
import Data.Functor (void)
import Data.Semigroup (Semigroup(..))
import Data.Word
import Foreign (ForeignPtr, Ptr, newForeignPtr_)
import Foreign.Marshal.Alloc (alloca)
import Foreign.Storable
import qualified Data.Array.Storable.Internals as Array
data InitError
= FailedToOpenTTY
| PipeTrapError
| UnsupportedTerminal
deriving (Show)
instance Exception InitError
main :: IO a -> IO a
main =
bracket_
(Tb.init >>= \case
Tb.InitOk -> pure ()
Tb.FailedToOpenTTY -> throwIO FailedToOpenTTY
Tb.PipeTrapError -> throwIO PipeTrapError
Tb.UnsupportedTerminal -> throwIO UnsupportedTerminal)
Tb.shutdown
size :: (width ~ Int, height ~ Int) => IO (width, height)
size =
(,) <$> Tb.width <*> Tb.height
setCursor :: (col ~ Int, row ~ Int) => col -> row -> IO ()
setCursor =
Tb.setCursor
hideCursor :: IO ()
hideCursor =
Tb.setCursor Tb._HIDE_CURSOR Tb._HIDE_CURSOR
data Cell
= Cell !Char !Attr !Attr
deriving (Eq)
instance Show Cell where
show (Cell ch fg bg) =
"Cell " ++ show ch ++ " " ++ show (attrToWord fg) ++ " " ++
show (attrToWord bg)
instance Storable Cell where
sizeOf :: Cell -> Int
sizeOf _ =
Tb.sizeofCell
alignment :: Cell -> Int
alignment _ =
Tb.alignofCell
peek :: Ptr Cell -> IO Cell
peek ptr =
Cell
<$> Tb.getCellCh ptr
<*> (wordToAttr <$> Tb.getCellFg ptr)
<*> (wordToAttr <$> Tb.getCellBg ptr)
poke :: Ptr Cell -> Cell -> IO ()
poke ptr (Cell ch fg bg) = do
Tb.setCellCh ptr ch
Tb.setCellFg ptr (attrToWord fg)
Tb.setCellBg ptr (attrToWord bg)
set :: (col ~ Int, row ~ Int) => col -> row -> Cell -> IO ()
set x y (Cell ch fg bg) =
Tb.changeCell x y ch (attrToWord fg) (attrToWord bg)
buffer :: (row ~ Int, col ~ Int) => IO (StorableArray (row, col) Cell)
buffer =
join
(mkbuffer
<$> (tb_cell_buffer >>= newForeignPtr_)
<*> Tb.width
<*> Tb.height)
where
mkbuffer
:: ForeignPtr Cell
-> Int
-> Int
-> IO (StorableArray (Int, Int) Cell)
mkbuffer buff w h =
Array.unsafeForeignPtrToStorableArray buff ((0, 0), (h-1, w-1))
clear :: (fg ~ Attr, bg ~ Attr) => fg -> bg -> IO ()
clear fg bg = do
Tb.setClearAttributes (attrToWord fg) (attrToWord bg)
Tb.clear
flush :: IO ()
flush =
Tb.present
data InputMode
= InputModeEsc MouseMode
| InputModeAlt MouseMode
deriving (Eq, Ord, Show)
data MouseMode
= MouseModeNo
| MouseModeYes
deriving (Eq, Ord, Show)
getInputMode :: IO InputMode
getInputMode =
f <$> Tb.selectInputMode Tb._INPUT_CURRENT
where
f :: Int -> InputMode
f = \case
1 -> InputModeEsc MouseModeNo
2 -> InputModeAlt MouseModeNo
5 -> InputModeEsc MouseModeYes
6 -> InputModeAlt MouseModeYes
n -> error ("getInputMode: " ++ show n)
setInputMode :: InputMode -> IO ()
setInputMode =
void . Tb.selectInputMode . f
where
f :: InputMode -> Int
f = \case
InputModeEsc MouseModeNo -> Tb._INPUT_ESC
InputModeEsc MouseModeYes -> Tb._INPUT_ESC .|. Tb._INPUT_MOUSE
InputModeAlt MouseModeNo -> Tb._INPUT_ALT
InputModeAlt MouseModeYes -> Tb._INPUT_ALT .|. Tb._INPUT_MOUSE
data OutputMode
= OutputModeNormal
| OutputModeGrayscale
| OutputMode216
| OutputMode256
deriving (Eq, Ord, Show)
getOutputMode :: IO OutputMode
getOutputMode =
f <$> Tb.selectOutputMode Tb.OutputModeCurrent
where
f :: Tb.OutputMode -> OutputMode
f = \case
Tb.OutputModeNormal -> OutputModeNormal
Tb.OutputMode256 -> OutputMode256
Tb.OutputMode216 -> OutputMode216
Tb.OutputModeGrayscale -> OutputModeGrayscale
Tb.OutputModeCurrent -> error "getOutputMode: OutputModeCurrent"
setOutputMode :: OutputMode -> IO ()
setOutputMode =
void . Tb.selectOutputMode . f
where
f :: OutputMode -> Tb.OutputMode
f = \case
OutputModeNormal -> Tb.OutputModeNormal
OutputMode256 -> Tb.OutputMode256
OutputMode216 -> Tb.OutputMode216
OutputModeGrayscale -> Tb.OutputModeGrayscale
data Event
= EventKey !Key !Bool
| EventResize !Int !Int
| EventMouse !Mouse !Int !Int
deriving (Eq, Show)
data Key
= KeyChar Char
| KeyArrowDown
| KeyArrowLeft
| KeyArrowRight
| KeyArrowUp
| KeyBackspace
| KeyBackspace2
| KeyCtrl2
| KeyCtrl3
| KeyCtrl4
| KeyCtrl5
| KeyCtrl6
| KeyCtrl7
| KeyCtrl8
| KeyCtrlA
| KeyCtrlB
| KeyCtrlBackslash
| KeyCtrlC
| KeyCtrlD
| KeyCtrlE
| KeyCtrlF
| KeyCtrlG
| KeyCtrlH
| KeyCtrlI
| KeyCtrlJ
| KeyCtrlK
| KeyCtrlL
| KeyCtrlLsqBracket
| KeyCtrlM
| KeyCtrlN
| KeyCtrlO
| KeyCtrlP
| KeyCtrlQ
| KeyCtrlR
| KeyCtrlRsqBracket
| KeyCtrlS
| KeyCtrlSlash
| KeyCtrlT
| KeyCtrlTilde
| KeyCtrlU
| KeyCtrlUnderscore
| KeyCtrlV
| KeyCtrlW
| KeyCtrlX
| KeyCtrlY
| KeyCtrlZ
| KeyDelete
| KeyEnd
| KeyEnter
| KeyEsc
| KeyF1
| KeyF10
| KeyF11
| KeyF12
| KeyF2
| KeyF3
| KeyF4
| KeyF5
| KeyF6
| KeyF7
| KeyF8
| KeyF9
| KeyHome
| KeyInsert
| KeyPageDn
| KeyPageUp
| KeySpace
| KeyTab
deriving (Eq, Ord, Show)
data Mouse
= MouseLeft
| MouseMiddle
| MouseRelease
| MouseRight
| MouseWheelDown
| MouseWheelUp
deriving (Eq, Ord, Show)
poll :: IO Event
poll =
alloca $ \ptr ->
Tb.pollEvent ptr >>= \case
-1 ->
throwIO PollError
_ ->
parseEvent <$> peek ptr
data PollError
= PollError
deriving Show
instance Exception PollError
parseEvent :: Tb.Event -> Event
parseEvent = \case
Tb.Event Tb.EventKey mod key ch _ _ _ _ ->
parseEventKey mod key ch
Tb.Event Tb.EventResize _ _ _ w h _ _ ->
EventResize w h
Tb.Event Tb.EventMouse _ key _ _ _ x y ->
EventMouse (parseMouse key) x y
parseEventKey :: Tb.Mod -> Tb.Key -> Char -> Event
parseEventKey mod key ch =
EventKey key' alt
where
key' :: Key
key' =
case ch of
'\0' -> parseKey key
_ -> KeyChar ch
alt :: Bool
alt =
case mod of
Tb.ModAlt -> True
_ -> False
parseKey :: Tb.Key -> Key
parseKey = \case
Tb.KeyArrowDown -> KeyArrowDown
Tb.KeyArrowLeft -> KeyArrowLeft
Tb.KeyArrowRight -> KeyArrowRight
Tb.KeyArrowUp -> KeyArrowUp
Tb.KeyBackspace -> KeyBackspace
Tb.KeyBackspace2 -> KeyBackspace2
Tb.KeyCtrl2 -> KeyCtrl2
Tb.KeyCtrl3 -> KeyCtrl3
Tb.KeyCtrl4 -> KeyCtrl4
Tb.KeyCtrl5 -> KeyCtrl5
Tb.KeyCtrl6 -> KeyCtrl6
Tb.KeyCtrl7 -> KeyCtrl7
Tb.KeyCtrl8 -> KeyCtrl8
Tb.KeyCtrlA -> KeyCtrlA
Tb.KeyCtrlB -> KeyCtrlB
Tb.KeyCtrlBackslash -> KeyCtrlBackslash
Tb.KeyCtrlC -> KeyCtrlC
Tb.KeyCtrlD -> KeyCtrlD
Tb.KeyCtrlE -> KeyCtrlE
Tb.KeyCtrlF -> KeyCtrlF
Tb.KeyCtrlG -> KeyCtrlG
Tb.KeyCtrlH -> KeyCtrlH
Tb.KeyCtrlI -> KeyCtrlI
Tb.KeyCtrlJ -> KeyCtrlJ
Tb.KeyCtrlK -> KeyCtrlK
Tb.KeyCtrlL -> KeyCtrlL
Tb.KeyCtrlLsqBracket -> KeyCtrlLsqBracket
Tb.KeyCtrlM -> KeyCtrlM
Tb.KeyCtrlN -> KeyCtrlN
Tb.KeyCtrlO -> KeyCtrlO
Tb.KeyCtrlP -> KeyCtrlP
Tb.KeyCtrlQ -> KeyCtrlQ
Tb.KeyCtrlR -> KeyCtrlR
Tb.KeyCtrlRsqBracket -> KeyCtrlRsqBracket
Tb.KeyCtrlS -> KeyCtrlS
Tb.KeyCtrlSlash -> KeyCtrlSlash
Tb.KeyCtrlT -> KeyCtrlT
Tb.KeyCtrlTilde -> KeyCtrlTilde
Tb.KeyCtrlU -> KeyCtrlU
Tb.KeyCtrlUnderscore -> KeyCtrlUnderscore
Tb.KeyCtrlV -> KeyCtrlV
Tb.KeyCtrlW -> KeyCtrlW
Tb.KeyCtrlX -> KeyCtrlX
Tb.KeyCtrlY -> KeyCtrlY
Tb.KeyCtrlZ -> KeyCtrlZ
Tb.KeyDelete -> KeyDelete
Tb.KeyEnd -> KeyEnd
Tb.KeyEnter -> KeyEnter
Tb.KeyEsc -> KeyEsc
Tb.KeyF1 -> KeyF1
Tb.KeyF10 -> KeyF10
Tb.KeyF11 -> KeyF11
Tb.KeyF12 -> KeyF12
Tb.KeyF2 -> KeyF2
Tb.KeyF3 -> KeyF3
Tb.KeyF4 -> KeyF4
Tb.KeyF5 -> KeyF5
Tb.KeyF6 -> KeyF6
Tb.KeyF7 -> KeyF7
Tb.KeyF8 -> KeyF8
Tb.KeyF9 -> KeyF9
Tb.KeyHome -> KeyHome
Tb.KeyInsert -> KeyInsert
Tb.KeyPageDn -> KeyPageDn
Tb.KeyPageUp -> KeyPageUp
Tb.KeySpace -> KeySpace
Tb.KeyTab -> KeyTab
key -> error ("parseKey: " ++ show key)
parseMouse :: Tb.Key -> Mouse
parseMouse = \case
Tb.KeyMouseLeft -> MouseLeft
Tb.KeyMouseMiddle -> MouseMiddle
Tb.KeyMouseRelease -> MouseRelease
Tb.KeyMouseRight -> MouseRight
Tb.KeyMouseWheelDown -> MouseWheelDown
Tb.KeyMouseWheelUp -> MouseWheelUp
key -> error ("parseMouse: " ++ show key)
data Attr
= Attr !Word16 !Word16
deriving (Eq)
instance Monoid Attr where
mempty :: Attr
mempty =
Attr Tb._DEFAULT 0
mappend :: Attr -> Attr -> Attr
mappend =
(<>)
instance Num Attr where
fromInteger :: Integer -> Attr
fromInteger n
| n >= 0 && n < 256 =
Attr (fromIntegral n) 0
| otherwise =
error ("Attr.fromInteger: " ++ show n ++ " out of range [0..255]")
(+) = error ("Attr.(+): not defined")
(*) = error ("Attr.(*): not defined")
(-) = error ("Attr.(-): not defined")
abs = error ("Attr.abs: not defined")
signum = error ("Attr.signum: not defined")
instance Semigroup Attr where
(<>) :: Attr -> Attr -> Attr
Attr 0 ax <> Attr cy ay = Attr cy (ax .|. ay)
Attr cx ax <> Attr 0 ay = Attr cx (ax .|. ay)
Attr cx ax <> Attr _ ay = Attr cx (ax .|. ay)
wordToAttr :: Word16 -> Attr
wordToAttr w =
Attr (w .&. 0x00FF) (w .&. 0xFF00)
attrToWord :: Attr -> Word16
attrToWord (Attr x y) =
x .|. y
black :: Attr
black =
Attr Tb._BLACK 0
red :: Attr
red =
Attr Tb._RED 0
green :: Attr
green =
Attr Tb._GREEN 0
yellow :: Attr
yellow =
Attr Tb._YELLOW 0
blue :: Attr
blue =
Attr Tb._BLUE 0
magenta :: Attr
magenta =
Attr Tb._MAGENTA 0
cyan :: Attr
cyan =
Attr Tb._CYAN 0
white :: Attr
white =
Attr Tb._WHITE 0
bold :: Attr
bold =
Attr Tb._DEFAULT Tb._BOLD
underline :: Attr
underline =
Attr Tb._DEFAULT Tb._UNDERLINE
reverse :: Attr
reverse =
Attr Tb._DEFAULT Tb._REVERSE
foreign import ccall safe "termbox.h tb_cell_buffer"
tb_cell_buffer :: IO (Ptr Cell)