escape-artist-1.1.0: ANSI Escape Sequence Text Decoration Made Easy

Copyright(c) Ryan Daniels 2016
LicenseBSD3
Maintainerrd.github@gmail.com
Stabilitystable
PortabilityTerminal supporting ANSI escape sequences
Safe HaskellSafe
LanguageHaskell2010

Text.EscapeArtist

Description

A library for text decoration with ANSI escape sequences made easy. Decorate your terminal text expressively. Any complex data type, existing or custom, can be simply colorized by implementing the class ToEscapable, then output to terminal or converted to String using the provided functions.

Simple Example

import Data.Monoid ((<>))
import Text.EscapeArtist

underlines = Underline $ FgCyan "I am underlined" <> UnderlineOff " but I am not " <> FgMagenta "and I am over here"

putEscLn underlines

Implementing ToEscapable

import Data.Monoid ((<>))
import Text.EscapeArtist

data ABC = A | B deriving (Show, Eq)

instance ToEscapable ABC where
   toEscapable (A) = FgRed $ show A
   toEscapable (B) = FgGreen $ show B

instance (ToEscapable a) => ToEscapable (Maybe a) where
    toEscapable (Just a) = FgGreen "Just" <> Inherit " " <> FgYellow a
    toEscapable a = FgRed $ show a

Notes

See the documentation on ToEscapable below for a more advanced example.

For GHC < 7.10 you will also need to explicitly derive Typeable for custom data types implementing ToEscapable. See the section Explicitly Derived Typeable in the documentation.

Comprehensive documentation with many examples here:

https://github.com/EarthCitizen/escape-artist#readme

Synopsis

Documentation

data Escapable Source #

The constructors used to apply attributes to values for terminal output

Constructors

ToEscapable a => FgBlack a

Foreground color black

ToEscapable a => FgRed a

Foreground color red

ToEscapable a => FgGreen a

Foreground color green

ToEscapable a => FgYellow a

Foreground color yellow

ToEscapable a => FgBlue a

Foreground color blue

ToEscapable a => FgMagenta a

Foreground color magenta

ToEscapable a => FgCyan a

Foreground color cyan

ToEscapable a => FgWhite a

Foreground color white

ToEscapable a => BgBlack a

Background color black

ToEscapable a => BgRed a

Background color red

ToEscapable a => BgGreen a

Background color green

ToEscapable a => BgYellow a

Background color yellow

ToEscapable a => BgBlue a

Background color blue

ToEscapable a => BgMagenta a

Background color magenta

ToEscapable a => BgCyan a

Background color cyan

ToEscapable a => BgWhite a

Background color white

ToEscapable a => FgDefault a

Applies default terminal foreground color

ToEscapable a => BgDefault a

Applies default terminal background color

ToEscapable a => Inherit a

Inherit attributes from the parent, but apply none directly

ToEscapable a => Default a

Applied value will have defaults of terminal

ToEscapable a => Blink a

Blinking text

ToEscapable a => BlinkOff a

Will not inherit blink attribute from parent

ToEscapable a => Bright a

Color mode to bright

ToEscapable a => BrightOff a

Will not inherit bright attribute from parent

ToEscapable a => Underline a

Underlined text

ToEscapable a => UnderlineOff a

Will not inherit underline attribute from parent

ToEscapable a => Inverse a

Swap the background and foreground colors

ToEscapable a => InverseOff a

Will not inherit inverse attribute from parent

class (Show a, Typeable a) => ToEscapable a where Source #

Implement ToEscapable by composing constructors of the type Escapable. This can be done for any data type with the exception of the following, which already come with an implementation which renders directly to String:

{-# LANGUAGE FlexibleInstances #-}

import Data.Monoid ((<>))
import Text.EscapeArtist

type FileName = String
type LineNumber = Integer
type ColumnNumber = Integer

data ErrorType = SyntaxError FileName LineNumber ColumnNumber deriving (Show)

instance ToEscapable ErrorType where
    toEscapable (SyntaxError fn ln cn) = Default "Syntax error in file "
                                       <> FgYellow ^$ Underline fn
                                       <> Default " at "
                                       <> FgRed (show ln ++ ":" ++ show cn)

instance ToEscapable (Either ErrorType String) where
    toEscapable (Left e) = toEscapable e
    toEscapable (Right m) = FgGreen m

mkSyntaxError :: FileName -> LineNumber -> ColumnNumber -> Either ErrorType String
mkSyntaxError fn ln cn = Left $ SyntaxError fn ln cn

mkStatusOK :: Either ErrorType String
mkStatusOK = Right "Status OK"

putEscLn $ mkSyntaxError "some/File.hs" 1 23
putEscLn mkStatusOK

Note: For GHC < 7.10 you will also need to explicitly derive Typeable for custom data types implementing ToEscapable. See the section Explicitly Derived Typeable in the documentation.

Minimal complete definition

toEscapable

Methods

toEscapable :: a -> Escapable Source #

Convert the given type to an Escapable

putEscLn :: ToEscapable a => a -> IO () Source #

Convert any instance of ToEscapable to a String and output it to the terminal followed by a newline

putEsc :: ToEscapable a => a -> IO () Source #

Convert any instance of ToEscapable to a String and output it to the terminal

escToString :: ToEscapable a => a -> String Source #

Convert any instance of ToEscapable to a String

(^$) :: (a -> b) -> a -> b infixr 7 Source #

The same as $, but with higher precedence. One level of precedence higher than <>. This allows avoiding parentheses when using $ and <> in the same expression. For example:

Underline $ (Bright $ FgGreen "GREEN") <> Default " " <> FgYellow "YELLOW"

can be written as:

Underline $ Bright ^$ FgGreen "GREEN" <> Default " " <> FgYellow "YELLOW"

In this example, Bright is applied only to the String "GREEN", that is concatenated with a space and the yellow text "YELLOW", then Underline is applied to the entire expression.