rainbow-0.2.0.0: Print text to terminal with colors and effects

Safe HaskellNone

System.Console.Rainbow

Contents

Description

Handles colors and special effects for text. Internally this module uses the Haskell terminfo library, which links against the UNIX library of the same name, so it should work with a wide variety of UNIX terminals.

The building block of Rainbow is the Chunk. Each Chunk comes with a TextSpec, which specifies how the text should look on 8-color and on 256-color terminals. The Chunk is a full specification; that is, although Chunks are typically printed one after the other, the appearance of one Chunk does not affect the appearance of the next Chunk.

You have full freedom to specify different attributes and colors for 8 and 256 color terminals; for instance, you can have text appear red on an 8-color terminal but blue on a 256-color terminal.

Some useful combinators are provided to assist with the building of Chunks. plain builds a Chunk with a provided Text that is rendered using the terminal's default settings and colors. You then use +.+ to combine different modifiers to change how the Chunk is rendered. Here's an example:

 {-# LANGUAGE OverloadedStrings #-}

 -- This chunk is blue and underlined, both on 8-color and 256-color
 -- terminals.
 blueHello :: Chunk
 blueHello = plain "Hello world!" +.+ f_blue +.+ underline

 -- This chunk is red on 8-color terminals but uses color 88 on
 -- 256-color terminals. Because +.+ is left-associative, the
 -- color256_f_88 supersedes the f_red, which sets the foreground
 -- on both 8 and 256 color terminals to red.
 redHello :: Chunk
 redHello = plain "Hello world!" +.+ f_red +.+ color256_f_88

 -- This chunk is underlined on 8-color terminals but is not
 -- underlined on 256-color terminals.
 underlinedOn8 :: Chunk
 underlinedOn8 = plain "Hello world!" +.+ underline8

 newline :: Chunk
 newline = plain "\n"

 -- How to print all these chunks
 main :: IO ()
 main = do
   t <- termFromEnv
   printChunks t [blueHello, nl, redHello, nl, underlinedOn8, nl]

Synopsis

Terminal definitions

data Term Source

Which terminal definition to use.

Constructors

Dumb

Using this terminal should always succeed. This suppresses all colors. Uesful if output is not going to a TTY, or if you just do not like colors.

TermName String

Use the terminal with this given name. You might get this from the TERM environment variable, or set it explicitly. A runtime error will result if the terminfo database does not have a definition for this terminal. If this terminal supports 256 colors, then 256 colors are used. If this terminal supports less than 256 colors, but at least 8 colors, then 8 colors are used. Otherwise, no colors are used.

Instances

termFromEnv :: IO TermSource

Gets the terminal definition from the environment. If the environment does not have a TERM veriable, use Dumb.

smartTermFromEnvSource

Arguments

:: Bool

Use True if the user always wants to see colors, even if standard output is not a terminal. Otherwise, use False.

-> Handle

Check this handle to see if it is a terminal (typically you will use stdout).

-> IO Term 

Gets the terminal definition from the environment. If the first argument is True, the terminal is always obtained from the environment. If it is False, the terminal is only obtained from the environment if the given handle is not a terminal; otherwise, Dumb is returned.

Chunks

data Chunk Source

A chunk is some textual data coupled with a description of what color the text is, attributes like whether it is bold or underlined, etc. The chunk knows what foreground and background colors and what attributes to use for both an 8 color terminal and a 256 color terminal. To change these attributes and colors, you must make a new chunk.

There is no way to combine chunks. To print large numbers of chunks, lazily build a list of them and then print them using printChunks.

Instances

plain :: Text -> ChunkSource

Makes a plain Chunk; that is, one that has no effects and is printed in the default foreground and background color for the terminal. Modify this chunk so that it has the colors and effects that you want.

Printing chunks

printChunks :: Term -> [Chunk] -> IO ()Source

Sends a list of chunks to standard output for printing. Sets up the terminal (this only needs to be done once.) Lazily processes the list of Chunk.

Which colors are used depends upon the Term. If it is Dumb, then no colors are used on output. If the Term is specified with TermName, the UNIX terminfo library is used to determine how many colors the terminal supports. If it supports at least 256 colors, then 256 colors are used. If it supports at least 8 colors but less than 256 colors, then 256 colors are used. Otherwise, no colors are used. A runtime error will occur if the TermName is not found in the system terminal database.

hPrintChunks :: Handle -> Term -> [Chunk] -> IO ()Source

Sends a list of chunks to the given handle for printing. Sets up the terminal (this only needs to be done once.) Lazily processes the list of Chunk. See printChunks for notes on how many colors are used.

Mod

class Mod a whereSource

A Mod is anything capable of modifying a Chunk. Usually these will modify the TextSpec, though a few Mod instead modify the Text itself. Typically you will create a Chunk with plain and then use +.+ repeatedly to modify the Chunk to suit your needs.

Methods

changeChunk :: Chunk -> a -> ChunkSource

Instances

Mod Text

When used as a modifier, a Text will replace the text within a Chunk with new text.

 {-# LANGUAGE OverloadedStrings #-}
 goodbyeWorld :: Chunk
 goodbyeWorld = plain "Hello world!" +.+ "Goodbye world!"
Mod BackgroundAll 
Mod ForegroundAll 
Mod InverseAll 
Mod FlashAll 
Mod UnderlineAll 
Mod BoldAll 
Mod Inverse256 
Mod Flash256 
Mod Underline256 
Mod Bold256 
Mod Inverse8 
Mod Flash8 
Mod Underline8 
Mod Bold8 
Mod Foreground256 
Mod Foreground8 
Mod Background256 
Mod Background8 
Mod ChangeText 

newtype ChangeText Source

Useful if you want to inspect the text in a Chunk and then build a new Chunk with different text.

 {-# LANGUAGE OverloadedStrings #-}
 import Data.Text (append)
 helloDolly :: Chunk
 helloDolly = plain "Hello" +.+ ChangeText (`append` " Dolly")

Constructors

ChangeText 

Fields

unChangeText :: Text -> Text
 

Instances

(.+.) :: Mod a => (Chunk -> Chunk) -> a -> Chunk -> ChunkSource

Composes modifiers. Useful to build up a single function that modifies a Chunk. You might use this to build up several modifiers and use them repeatedly, or you might write an API that expects functions of type Chunk -> Chunk and then you could use .+. to build those functions. Left associative.

 redBoldUnderline :: Chunk -> Chunk
 redBoldUnderline = id .+. f_red .+. bold .+. underline

(+.+) :: Mod a => Chunk -> a -> ChunkSource

Applies a modifier to a Chunk. Left associative.

Effects for both 8 and 256 color terminals

These modifiers affect both 8 and 256 color terminals:

 {-# LANGUAGE OverloadedStrings #-}
 underlinedOn8and256 :: Chunk
 underlinedOn8and256 = plain "Underlined!" +.+ underline

There are also modifiers to turn an effect off, such as boldOff. Ordinarily you will not need these because each chunk starts with no effects, so you only need to turn on the effects you want. However the off modifiers are here if you need them.

Effects for 8-color terminals only

These modifiers affect 8-color terminals only. For instance this appears bold only on an 8-color terminal:

 {-# LANGUAGE OverloadedStrings #-}
 boldOn8 :: Chunk
 boldOn8 = plain "Bold on 8 color terminal only" +.+ bold8

Effects for 256-color terminals only

These modifiers affect 256-color terminals only. For instance, this text is underlined on 256 color terminals but is bold on 8-color terminals:

 {-# LANGUAGE OverloadedStrings #-}
 underlinedOn256 :: Chunk
 underlinedOn256 = plain "Underlined on 256 color terminal"
                 +.+ underlined256 +.+ bold8

Colors for both 8 and 256 color terminals

These color modifiers affect both 8 and 256 color terminals. For example, to print something in red on blue on both an 8 and a 256 color terminal:

 {-# LANGUAGE OverloadedStrings #-}
 redHello :: Chunk
 redHello = plain "Hello world!" +.+ f_red +.+ b_blue

Foreground colors

Background colors

Specific colors

8 color foreground colors

8 color background colors

256 color foreground colors

The color names assume a palette similar to the default one that xterm uses.

256 color background colors

The color names assume a palette similar to the default one that xterm uses.

Create your own colors

Style, TextSpec, and Chunk innards

A style is a bundle of attributes that describes text attributes, such as its color and whether it is bold.

Ordinarily you shouldn't need to use these types but they are here in case they are useful; in particular, you can use them to examine a Chunk's TextSpec to see what its characteristics are.

data StyleCommon Source

Style elements that apply in both 8 and 256 color terminals. However, the elements are described separately for 8 and 256 color terminals, so that the text appearance can change depending on how many colors a terminal has.

data Style8 Source

Describes text appearance (foreground and background colors, as well as other attributes such as bold) for an 8 color terminal.

Instances

data Style256 Source

Describes text appearance (foreground and background colors, as well as other attributes such as bold) for a 256 color terminal.

defaultStyleCommon :: StyleCommonSource

Has all bold, flash, underline, and inverse turned off.

defaultStyle8 :: Style8Source

Uses the default terminal colors (which will vary depending on the terminal).

defaultStyle256 :: Style256Source

Uses the default terminal colors (which will vary depending on the terminal).

data TextSpec Source

The TextSpec bundles together the styles for the 8 and 256 color terminals, so that the text can be portrayed on any terminal.

Constructors

TextSpec 

defaultTextSpec :: TextSpecSource

A TextSpec with the default colors on 8 and 256 color terminals, with all attributes turned off.

Basement

Ordinarily you will not need the things down here. Instead, the definitions above will give you an instance of Mod that will create the effect or color you need.

Modifier newtype wrappers

newtype Bold8 Source

Constructors

Bold8 

Fields

unBold8 :: Bold
 

newtype Flash8 Source

Constructors

Flash8 

Fields

unFlash8 :: Flash
 

newtype Inverse8 Source

Constructors

Inverse8 

Fields

unInverse8 :: Inverse
 

newtype Bold256 Source

Constructors

Bold256 

Fields

unBold256 :: Bold
 

newtype Flash256 Source

Constructors

Flash256 

Fields

unFlash256 :: Flash
 

newtype BoldAll Source

Constructors

BoldAll 

Fields

unBoldAll :: Bool
 

newtype FlashAll Source

Constructors

FlashAll 

Fields

unFlashAll :: Bool
 

Wrappers for effects

newtype Bold Source

Constructors

Bold 

Fields

unBold :: Bool
 

Instances

newtype Underline Source

Constructors

Underline 

Fields

unUnderline :: Bool
 

newtype Flash Source

Constructors

Flash 

Fields

unFlash :: Bool
 

Instances

newtype Inverse Source

Constructors

Inverse 

Fields

unInverse :: Bool
 

Wrappers for colors

Definitions are provided above that give you every possible color; however, these constructors are exported in case you want to make your own colors instead. Use at your own risk, as you can create non-sensical colors with this (such as 256-color colors in a Background8.)

newtype Background8 Source

Background color in an 8 color setting.

Constructors

Background8 

newtype Background256 Source

Background color in a 256 color setting.

Constructors

Background256 

newtype Foreground8 Source

Foreground color in an 8 color setting.

Constructors

Foreground8 

newtype Foreground256 Source

Foreground color in a 256 color setting.

Constructors

Foreground256