terminfo-0.2.2.1: Haskell bindings to the terminfo library.

Portabilityportable (FFI)
Stabilityexperimental
Maintainerjudah.jacobson@gmail.com

System.Console.Terminfo.Base

Contents

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

Documentation

setupTerm :: String -> IO TerminalSource

Initialize the terminfo library to the given terminal entry.

setupTermFromEnv :: IO TerminalSource

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

data Capability a Source

A feature or operation which a Terminal may define.

tiGetFlag :: String -> Capability BoolSource

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 IntSource

Look up a numeric capability in the terminfo database.

tiGetStr :: String -> Capability StringSource

Look up a string capability in the terminfo database.

Note: Do not use this function for terminal output; use tiGetOutput instead.

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.

termText :: String -> TermOutputSource

Output plain text containing no control characters or escape sequences.

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

Look up an output capability in the terminfo database.

type LinesAffected = IntSource

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.

tiGetOutput1 :: OutputCap f => String -> Capability fSource

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

A type class to encapsulate capabilities which take in zero or more parameters.

Instances

Monoid functions

class Monoid a where

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Minimal complete definition: mempty and mappend.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Methods

mempty :: a

Identity of mappend

mappend :: a -> a -> a

An associative operation

mconcat :: [a] -> a

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 
Monoid All 
Monoid Any 
Monoid TermOutput 
Monoid [a] 
Monoid a => Monoid (Dual a) 
Monoid (Endo a) 
Num a => Monoid (Sum a) 
Num a => Monoid (Product a) 
Monoid (First a) 
Monoid (Last a) 
Monoid a => Monoid (Maybe a) 
Monoid b => Monoid (a -> b) 
(Monoid a, Monoid b) => Monoid (a, b) 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) 

(<#>) :: Monoid m => m -> m -> mSource

An operator version of mappend.