Maintainer | judah.jacobson@gmail.com |
---|---|
Stability | experimental |
Portability | portable (FFI) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
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
- data Terminal
- setupTerm :: String -> IO Terminal
- setupTermFromEnv :: IO Terminal
- data SetupTermError
- data Capability a
- getCapability :: Terminal -> Capability a -> Maybe a
- tiGetFlag :: String -> Capability Bool
- tiGuardFlag :: String -> Capability ()
- tiGetNum :: String -> Capability Int
- tiGetStr :: String -> Capability String
- tiGetOutput1 :: forall f. OutputCap f => String -> Capability f
- class OutputCap f
- class (Monoid s, OutputCap s) => TermStr s
- data TermOutput
- runTermOutput :: Terminal -> TermOutput -> IO ()
- hRunTermOutput :: Handle -> Terminal -> TermOutput -> IO ()
- termText :: String -> TermOutput
- tiGetOutput :: String -> Capability ([Int] -> LinesAffected -> TermOutput)
- type LinesAffected = Int
- class Semigroup a => Monoid a where
- (<#>) :: Monoid m => m -> m -> m
Initialization
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 multipleTerminal
s 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.
data SetupTermError Source #
Instances
Exception SetupTermError Source # | |
Defined in System.Console.Terminfo.Base | |
Show SetupTermError Source # | |
Defined in System.Console.Terminfo.Base showsPrec :: Int -> SetupTermError -> ShowS # show :: SetupTermError -> String # showList :: [SetupTermError] -> ShowS # |
Capabilities
data Capability a Source #
A feature or operation which a Terminal
may define.
Instances
getCapability :: Terminal -> Capability a -> Maybe a Source #
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.
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 String
s. 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 :: forall f. 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.
hasOkPadding, outputCap
Instances
OutputCap TermOutput Source # | |
Defined in System.Console.Terminfo.Base hasOkPadding :: TermOutput -> String -> Bool outputCap :: ([Int] -> String) -> [Int] -> TermOutput | |
OutputCap [Char] Source # | |
Defined in System.Console.Terminfo.Base | |
(Enum p, OutputCap f) => OutputCap (p -> f) Source # | |
Defined in System.Console.Terminfo.Base |
class (Monoid s, OutputCap s) => TermStr s Source #
Instances
TermStr TermOutput Source # | |
Defined in System.Console.Terminfo.Base | |
TermStr [Char] Source # | |
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.
Instances
Monoid TermOutput Source # | |
Defined in System.Console.Terminfo.Base mempty :: TermOutput # mappend :: TermOutput -> TermOutput -> TermOutput # mconcat :: [TermOutput] -> TermOutput # | |
Semigroup TermOutput Source # | |
Defined in System.Console.Terminfo.Base (<>) :: TermOutput -> TermOutput -> TermOutput # sconcat :: NonEmpty TermOutput -> TermOutput # stimes :: Integral b => b -> TermOutput -> TermOutput # | |
OutputCap TermOutput Source # | |
Defined in System.Console.Terminfo.Base hasOkPadding :: TermOutput -> String -> Bool outputCap :: ([Int] -> String) -> [Int] -> TermOutput | |
TermStr TermOutput Source # | |
Defined in System.Console.Terminfo.Base |
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 -> TermOutput Source #
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 #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
x
<>
mempty
= x- Left identity
mempty
<>
x = x- Associativity
x
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
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 newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Identity of mappend
>>>
"Hello world" <> mempty
"Hello world"
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
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.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Monoid All | Since: base-2.1 |
Monoid Any | Since: base-2.1 |
Monoid Ordering | Since: base-2.1 |
Monoid TermOutput Source # | |
Defined in System.Console.Terminfo.Base mempty :: TermOutput # mappend :: TermOutput -> TermOutput -> TermOutput # mconcat :: [TermOutput] -> TermOutput # | |
Monoid () | Since: base-2.1 |
(Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
Monoid a => Monoid (Dual a) | Since: base-2.1 |
Monoid (Endo a) | Since: base-2.1 |
Num a => Monoid (Product a) | Since: base-2.1 |
Num a => Monoid (Sum a) | Since: base-2.1 |
Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (a) | Since: base-4.15 |
Monoid [a] | Since: base-2.1 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Monoid b => Monoid (a -> b) | Since: base-2.1 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 |