module Termbox.Bindings.Hs.Internal.InitError
( Tb_init_error
( Tb_init_error,
TB_EFAILED_TO_OPEN_TTY,
TB_EPIPE_TRAP_ERROR,
TB_EUNSUPPORTED_TERMINAL
),
)
where
import Foreign.C.Types (CInt)
import qualified Termbox.Bindings.C
newtype Tb_init_error
= Tb_init_error CInt
deriving stock (Tb_init_error -> Tb_init_error -> Bool
(Tb_init_error -> Tb_init_error -> Bool)
-> (Tb_init_error -> Tb_init_error -> Bool) -> Eq Tb_init_error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tb_init_error -> Tb_init_error -> Bool
== :: Tb_init_error -> Tb_init_error -> Bool
$c/= :: Tb_init_error -> Tb_init_error -> Bool
/= :: Tb_init_error -> Tb_init_error -> Bool
Eq, Eq Tb_init_error
Eq Tb_init_error =>
(Tb_init_error -> Tb_init_error -> Ordering)
-> (Tb_init_error -> Tb_init_error -> Bool)
-> (Tb_init_error -> Tb_init_error -> Bool)
-> (Tb_init_error -> Tb_init_error -> Bool)
-> (Tb_init_error -> Tb_init_error -> Bool)
-> (Tb_init_error -> Tb_init_error -> Tb_init_error)
-> (Tb_init_error -> Tb_init_error -> Tb_init_error)
-> Ord Tb_init_error
Tb_init_error -> Tb_init_error -> Bool
Tb_init_error -> Tb_init_error -> Ordering
Tb_init_error -> Tb_init_error -> Tb_init_error
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Tb_init_error -> Tb_init_error -> Ordering
compare :: Tb_init_error -> Tb_init_error -> Ordering
$c< :: Tb_init_error -> Tb_init_error -> Bool
< :: Tb_init_error -> Tb_init_error -> Bool
$c<= :: Tb_init_error -> Tb_init_error -> Bool
<= :: Tb_init_error -> Tb_init_error -> Bool
$c> :: Tb_init_error -> Tb_init_error -> Bool
> :: Tb_init_error -> Tb_init_error -> Bool
$c>= :: Tb_init_error -> Tb_init_error -> Bool
>= :: Tb_init_error -> Tb_init_error -> Bool
$cmax :: Tb_init_error -> Tb_init_error -> Tb_init_error
max :: Tb_init_error -> Tb_init_error -> Tb_init_error
$cmin :: Tb_init_error -> Tb_init_error -> Tb_init_error
min :: Tb_init_error -> Tb_init_error -> Tb_init_error
Ord)
instance Show Tb_init_error where
show :: Tb_init_error -> String
show = \case
Tb_init_error
TB_EFAILED_TO_OPEN_TTY -> String
"TB_EFAILED_TO_OPEN_TTY"
Tb_init_error
TB_EPIPE_TRAP_ERROR -> String
"TB_EPIPE_TRAP_ERROR"
Tb_init_error
TB_EUNSUPPORTED_TERMINAL -> String
"TB_EUNSUPPORTED_TERMINAL"
pattern TB_EFAILED_TO_OPEN_TTY :: Tb_init_error
pattern $mTB_EFAILED_TO_OPEN_TTY :: forall {r}. Tb_init_error -> ((# #) -> r) -> ((# #) -> r) -> r
$bTB_EFAILED_TO_OPEN_TTY :: Tb_init_error
TB_EFAILED_TO_OPEN_TTY <-
((== Tb_init_error Termbox.Bindings.C._TB_EFAILED_TO_OPEN_TTY) -> True)
where
TB_EFAILED_TO_OPEN_TTY = CInt -> Tb_init_error
Tb_init_error CInt
Termbox.Bindings.C._TB_EFAILED_TO_OPEN_TTY
pattern TB_EPIPE_TRAP_ERROR :: Tb_init_error
pattern $mTB_EPIPE_TRAP_ERROR :: forall {r}. Tb_init_error -> ((# #) -> r) -> ((# #) -> r) -> r
$bTB_EPIPE_TRAP_ERROR :: Tb_init_error
TB_EPIPE_TRAP_ERROR <-
((== Tb_init_error Termbox.Bindings.C._TB_EPIPE_TRAP_ERROR) -> True)
where
TB_EPIPE_TRAP_ERROR = CInt -> Tb_init_error
Tb_init_error CInt
Termbox.Bindings.C._TB_EPIPE_TRAP_ERROR
pattern TB_EUNSUPPORTED_TERMINAL :: Tb_init_error
pattern $mTB_EUNSUPPORTED_TERMINAL :: forall {r}. Tb_init_error -> ((# #) -> r) -> ((# #) -> r) -> r
$bTB_EUNSUPPORTED_TERMINAL :: Tb_init_error
TB_EUNSUPPORTED_TERMINAL <-
((== Tb_init_error Termbox.Bindings.C._TB_EUNSUPPORTED_TERMINAL) -> True)
where
TB_EUNSUPPORTED_TERMINAL = CInt -> Tb_init_error
Tb_init_error CInt
Termbox.Bindings.C._TB_EUNSUPPORTED_TERMINAL
{-# COMPLETE TB_EFAILED_TO_OPEN_TTY, TB_EPIPE_TRAP_ERROR, TB_EUNSUPPORTED_TERMINAL #-}