console-style-0.0.2.1: Styled console text output using ANSI escape sequences.

CopyrightDaniel Mendler (c) 2016
LicenseMIT (see the file LICENSE)
Maintainermail@daniel-mendler.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

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.

Synopsis

Documentation

data Color Source #

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.

Instances

Eq Color Source # 

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color Source # 

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

class HasStyle s where Source #

State accessor for the Style

Minimal complete definition

getStyle, putStyle

Methods

getStyle :: s -> Style Source #

putStyle :: Style -> s -> s Source #

data SetStyle Source #

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 

data Style Source #

Abstract state datatype which keeps a stack of the applied styles.

data Term Source #

Terminal type. For less capable terminals the color depth is automatically reduced.

Constructors

TermDumb

Dumb terminal - no color output

Term8

8 colors supported

Term256

256 colors supported

TermRGB

True colors supported

TermWin

Windows terminal. Will use emulation (Not yet implemented).

Instances

Eq Term Source # 

Methods

(==) :: Term -> Term -> Bool #

(/=) :: Term -> Term -> Bool #

Show Term Source # 

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

defaultStyle :: Term -> Style Source #

The function (defaultStyle term) returns the default Style configured with terminal type term.

hDefaultStyle :: Handle -> Term -> Style Source #

(hDefaultStyle handle term) return the default (initial) Style configured with the file handle handle and terminal type term@.

Every Style has a single associated handle.

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.

hRunStyle :: MonadIO m => Handle -> StateT Style m a -> m a Source #

The action (hRunStyle handle action) runs the StateT monad transformer providing the active Style for the given action.

hRunWithStyle :: (MonadIO m, Foldable f) => Handle -> f SetStyle -> StateT Style m a -> m a Source #

The action (hRunWithStyle handle cmd action) runs the StateT monad transformer providing the active Style for the given action.

The output on handle within the action is modified by the given StyleSet commands cmd. The Style is restored to the defaults afterwards.

runStyle :: Term -> State Style a -> a Source #

The action (runStyle term action) runs the State monad providing the active Style for the given action.

runStyleT :: Monad m => Term -> StateT Style m a -> m a Source #

The action (runStyleT term action) runs the StateT monad transformer providing the active Style for the given action.

runWithStyle :: (MonadIO m, Foldable f) => f SetStyle -> StateT Style m a -> m a Source #

The action (runWithStyle cmd action) runs the StateT monad transformer providing the active Style for the given action.

The output on stdout within the action is modified by the given StyleSet commands cmd. The Style is restored to the defaults afterwards.

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 #

The action (withStyle cmd action) executes the action with the active Style modified by the StyleSet commands cmd.

The style is restored to the previous Style afterwards.

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.