terminfo-0.4.1.6: Haskell bindings to the terminfo library.
Maintainerjudah.jacobson@gmail.com
Stabilityexperimental
Portabilityportable (FFI)
Safe HaskellTrustworthy
LanguageHaskell2010

System.Console.Terminfo.Base

Description

This module provides a low-level interface to the C functions of the terminfo library.

NOTE: Since this library is built on top of the curses interface, it is not thread-safe.

Synopsis

Initialization

data Terminal Source #

Terminal objects are automatically freed by the garbage collector. Hence, there is no equivalent of del_curterm here.

setupTerm :: String -> IO Terminal Source #

Initialize the terminfo library to the given terminal entry.

Throws a SetupTermError if the terminfo database could not be read.

  • Note:* ncurses is not thread-safe; initializing or using multiple Terminals in different threads at the same time can result in memory unsafety.

setupTermFromEnv :: IO Terminal Source #

Initialize the terminfo library, using the TERM environmental variable. If TERM is not set, we use the generic, minimal entry dumb.

Throws a SetupTermError if the terminfo database could not be read.

Capabilities

data Capability a Source #

A feature or operation which a Terminal may define.

Instances

Instances details
Alternative Capability Source # 
Instance details

Defined in System.Console.Terminfo.Base

Applicative Capability Source # 
Instance details

Defined in System.Console.Terminfo.Base

Methods

pure :: a -> Capability a #

(<*>) :: Capability (a -> b) -> Capability a -> Capability b #

liftA2 :: (a -> b -> c) -> Capability a -> Capability b -> Capability c #

(*>) :: Capability a -> Capability b -> Capability b #

(<*) :: Capability a -> Capability b -> Capability a #

Functor Capability Source # 
Instance details

Defined in System.Console.Terminfo.Base

Methods

fmap :: (a -> b) -> Capability a -> Capability b #

(<$) :: a -> Capability b -> Capability a #

Monad Capability Source # 
Instance details

Defined in System.Console.Terminfo.Base

Methods

(>>=) :: Capability a -> (a -> Capability b) -> Capability b #

(>>) :: Capability a -> Capability b -> Capability b #

return :: a -> Capability a #

MonadPlus Capability Source # 
Instance details

Defined in System.Console.Terminfo.Base

tiGetFlag :: String -> Capability Bool Source #

Look up a boolean capability in the terminfo database.

Unlike tiGuardFlag, this capability never fails; it returns False if the capability is absent or set to false, and returns True otherwise.

tiGuardFlag :: String -> Capability () Source #

Look up a boolean capability in the terminfo database, and fail if it's not defined.

tiGetNum :: String -> Capability Int Source #

Look up a numeric capability in the terminfo database.

tiGetStr :: String -> Capability String Source #

Deprecated: use tiGetOutput instead.

Look up a string capability in the terminfo database. NOTE: This function is deprecated; use tiGetOutput1 instead.

Output

Terminfo contains many string capabilities for special effects. For example, the cuu1 capability moves the cursor up one line; on ANSI terminals this is accomplished by printing the control sequence "\ESC[A". However, some older terminals also require "padding", or short pauses, after certain commands. For example, when TERM=vt100 the cuu1 capability is "\ESC[A$<2>", which instructs terminfo to pause for two milliseconds after outputting the control sequence.

The TermOutput monoid abstracts away all padding and control sequence output. Unfortunately, that datatype is difficult to integrate into existing String-based APIs such as pretty-printers. Thus, as a workaround, tiGetOutput1 also lets us access the control sequences as Strings. The one caveat is that it will not allow you to access padded control sequences as Strings. For example:

> t <- setupTerm "vt100"
> isJust (getCapability t (tiGetOutput1 "cuu1") :: Maybe String)
False
> isJust (getCapability t (tiGetOutput1 "cuu1") :: Maybe TermOutput)
True

String capabilities will work with software-based terminal types such as xterm and linux. However, you should use TermOutput if compatibility with older terminals is important. Additionally, the visualBell capability which flashes the screen usually produces its effect with a padding directive, so it will only work with TermOutput.

tiGetOutput1 :: OutputCap f => String -> Capability f Source #

Look up an output capability which takes a fixed number of parameters (for example, Int -> Int -> TermOutput).

For capabilities which may contain variable-length padding, use tiGetOutput instead.

class OutputCap f Source #

Minimal complete definition

hasOkPadding, outputCap

Instances

Instances details
OutputCap TermOutput Source # 
Instance details

Defined in System.Console.Terminfo.Base

OutputCap [Char] Source # 
Instance details

Defined in System.Console.Terminfo.Base

Methods

hasOkPadding :: [Char] -> String -> Bool

outputCap :: ([Int] -> String) -> [Int] -> [Char]

(Enum p, OutputCap f) => OutputCap (p -> f) Source # 
Instance details

Defined in System.Console.Terminfo.Base

Methods

hasOkPadding :: (p -> f) -> String -> Bool

outputCap :: ([Int] -> String) -> [Int] -> p -> f

class (Monoid s, OutputCap s) => TermStr s Source #

Instances

Instances details
TermStr TermOutput Source # 
Instance details

Defined in System.Console.Terminfo.Base

TermStr [Char] Source # 
Instance details

Defined in System.Console.Terminfo.Base

TermOutput

data TermOutput Source #

An action which sends output to the terminal. That output may mix plain text with control characters and escape sequences, along with delays (called "padding") required by some older terminals.

runTermOutput :: Terminal -> TermOutput -> IO () Source #

Write the terminal output to the standard output device.

hRunTermOutput :: Handle -> Terminal -> TermOutput -> IO () Source #

Write the terminal output to the terminal or file managed by the given Handle.

tiGetOutput :: String -> Capability ([Int] -> LinesAffected -> TermOutput) Source #

Look up an output capability in the terminfo database.

type LinesAffected = Int Source #

A parameter to specify the number of lines affected. Some capabilities (e.g., clear and dch1) use this parameter on some terminals to compute variable-length padding.

Monoid functions

class Semigroup a => Monoid a where #

Minimal complete definition

mempty | mconcat

Methods

mempty :: a #

mappend :: a -> a -> a #

mconcat :: [a] -> a #

Instances

Instances details
Monoid ByteArray

Since: base-4.17.0.0

Instance details

Defined in Data.Array.Byte

Monoid Ordering 
Instance details

Defined in GHC.Internal.Base

Monoid TermOutput Source # 
Instance details

Defined in System.Console.Terminfo.Base

Monoid () 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid (Comparison a)

mempty on comparisons always returns EQ. Without newtypes this equals pure (pure EQ).

mempty :: Comparison a
mempty = Comparison _ _ -> EQ
Instance details

Defined in Data.Functor.Contravariant

Monoid (Equivalence a)

mempty on equivalences always returns True. Without newtypes this equals pure (pure True).

mempty :: Equivalence a
mempty = Equivalence _ _ -> True
Instance details

Defined in Data.Functor.Contravariant

Monoid (Predicate a)

mempty on predicates always returns True. Without newtypes this equals pure True.

mempty :: Predicate a
mempty = _ -> True
Instance details

Defined in Data.Functor.Contravariant

(Ord a, Bounded a) => Monoid (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

(Ord a, Bounded a) => Monoid (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid a => Monoid (IO a) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Semigroup a => Monoid (Maybe a) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (Solo a) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: Solo a #

mappend :: Solo a -> Solo a -> Solo a #

mconcat :: [Solo a] -> Solo a #

Monoid [a] 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid a => Monoid (Op a b)

mempty @(Op a b) without newtypes is mempty @(b->a) = _ -> mempty.

mempty :: Op a b
mempty = Op _ -> mempty
Instance details

Defined in Data.Functor.Contravariant

Methods

mempty :: Op a b #

mappend :: Op a b -> Op a b -> Op a b #

mconcat :: [Op a b] -> Op a b #

(Monoid a, Monoid b) => Monoid (a, b) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid b => Monoid (a -> b) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

mempty :: Product f g a #

mappend :: Product f g a -> Product f g a -> Product f g a #

mconcat :: [Product f g a] -> Product f g a #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

Monoid (f (g a)) => Monoid (Compose f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Compose

Methods

mempty :: Compose f g a #

mappend :: Compose f g a -> Compose f g a -> Compose f g a #

mconcat :: [Compose f g a] -> Compose f g a #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 
Instance details

Defined in GHC.Internal.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

(<#>) :: Monoid m => m -> m -> m infixl 2 Source #

An operator version of mappend.