console-style-0.0.1.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 supports is currently not implemented, but is planned (by using ansi-terminal or by directly using 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

class HasStyle s where Source #

Minimal complete definition

getStyle, putStyle

Methods

getStyle :: s -> Style Source #

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

data Term Source #

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 #

(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 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 style 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.

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 style 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 current style by executing the style commands cmd.

styleCode' :: Foldable f => Style -> f SetStyle -> (Style, String) Source #

The function (styleCode' style cmd) returns the modified style status and ANSI code corresponding to the style commands cmd.

styleCode :: (MonadState s m, HasStyle s, Foldable f) => f SetStyle -> m String Source #

The action (styleCode cmd) returns the ANSI code corresponding to the style commands cmd. This action must be executed within a monadic context providing the current style status.

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 current style modified by the style commands cmd.

The style is restored to the previously active style afterwards.