Copyright | Daniel Mendler (c) 2016 |
---|---|
License | MIT (see the file LICENSE) |
Maintainer | mail@daniel-mendler.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
System.Console.Style
Description
This library provides styled text output using ANSI escape sequences. The main feature is that the library keeps track of a stack of the active styles using a state monad. This makes it easy to use this library for a pretty printer with nested annotations, e.g., wl-pprint-console.
Warning: Windows support is currently not implemented, but is planned (by using ansi-terminal or the ffi).
Example:
basicExample :: IO () basicExample = runWithStyle [FgColor Blue] $ do withStyle [Bold] $ liftIO $ putStr "Bold Blue" setStyle [Save, Italic, BgColor Red] liftIO $ putStr "Italic Red" setStyle [Restore] setStyle [Under] liftIO $ putStr "Under Blue" setStyle [Reset] liftIO $ putStrLn "Normal output"
For many more examples, see the Example.hs file.
- data Color
- class HasStyle s where
- data SetStyle
- data Style
- data Term
- defaultStyle :: Term -> Style
- hDefaultStyle :: Handle -> Term -> Style
- hGetTerm :: MonadIO m => Handle -> m Term
- hRunStyle :: MonadIO m => Handle -> StateT Style m a -> m a
- hRunWithStyle :: (MonadIO m, Foldable f) => Handle -> f SetStyle -> StateT Style m a -> m a
- runStyle :: Term -> State Style a -> a
- runStyleT :: Monad m => Term -> StateT Style m a -> m a
- runWithStyle :: (MonadIO m, Foldable f) => f SetStyle -> StateT Style m a -> m a
- setStyle :: (MonadIO m, MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m ()
- setStyleCode :: (MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m String
- withStyle :: (MonadIO m, MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m a -> m a
- changeStyle :: (MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m ()
- applyStyle :: (MonadIO m, MonadState s m, HasStyle s) => m ()
- applyStyleCode :: (MonadState s m, HasStyle s) => m String
Documentation
Console color
Constructors
DefaultColor | Default terminal color (terminal specific) |
Black | |
Red | |
Green | |
Yellow | |
Blue | |
Magenta | |
Cyan | |
White | |
DullBlack | |
DullRed | |
DullGreen | |
DullYellow | |
DullBlue | |
DullMagenta | |
DullCyan | |
DullWhite | |
Color256 !Word8 | Color from 256 color scheme. Color is automatically reduced to 8 colors for less capable terminals. |
RGB !Word8 !Word8 !Word8 | True color. Color is automatically reduced to 256 or 8 colors for less capable terminals. |
Style commands
Constructors
Bold | Bold font |
NotBold | Normal-weight font |
Italic | Italic font |
NotItalic | Non-italic font |
Under | Underlined text |
NotUnder | Text without underline |
Invert | Invert foreground and background color |
NotInvert | Deactivate color inversion |
Save | Save style to stack |
Restore | Restore style from stack |
Reset | Reset to default style |
Blink | Activate blinking |
NotBlink | Deactivate blinking |
FgColor !Color | |
BgColor !Color |
Abstract state datatype which keeps a stack of the applied styles.
Terminal type. For less capable terminals the color depth is automatically reduced.
defaultStyle :: Term -> Style Source #
The function (defaultStyle term)
returns the default Style
configured with terminal type term
.
hGetTerm :: MonadIO m => Handle -> m Term Source #
The action (hGetTerm handle)
determines the terminal type of the file handle
.
The terminal type is determined by checking if the file handle points to a device
and by looking at the $TERM
environment variable.
hRunWithStyle :: (MonadIO m, Foldable f) => Handle -> f SetStyle -> StateT Style m a -> m a Source #
setStyle :: (MonadIO m, MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m () Source #
The action (setStyle cmd)
modifies the active Style
by executing the StyleSet
commands cmd
.
The style changes are applied immediately.
setStyleCode :: (MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m String Source #
The action (styleCode cmd)
returns the ANSI code corresponding to the StyleSet
commands cmd
.
withStyle :: (MonadIO m, MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m a -> m a Source #
changeStyle :: (MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m () Source #
The action (changeStyle cmd)
modifies the active Style
by executing the StyleSet
commands cmd
without applying the changes.
You have to call applyStyle or applyStyleCode afterwards!
applyStyle :: (MonadIO m, MonadState s m, HasStyle s) => m () Source #
The action applyStyle
applies the latest style changes.
applyStyleCode :: (MonadState s m, HasStyle s) => m String Source #
The action applyStyleCode
returns the ANSI code for the latest style changes.