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

Safe HaskellNone

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.

A Chunk is a Monoid, so you can combine them using the usual monoid functions, including <>. You can create a Chunk with text using fromString, but this library is much more usable if you enable the OverloadedStrings GHC extension:

 {-# LANGUAGE OverloadedStrings #-}

and all future examples assume you have enabled OverloadedStrings. You will also want the Monoid module in scope:

 import Data.Monoid

Here are some basic examples:

 putChunkLn $ Some blue text  fore blue
 putChunkLn $ Blue on red background
                 fore blue  back red
 putChunkLn $ Blue on red, foreground bold
                 fore blue  back red  bold

But what makes Rainbow a little more interesting is that you can also specify output for 256-color terminals. To use these examples, be sure your TERM environment variable is set to something that supports 256 colors (like xterm-256color) before you start GHCi:

 putChunkLn $ Blue on 8-color terminal, red on 256-color terminal
                  fore blue8  back (to256 red)

To get a Color256, which affects only 256-color terminals, there are some definitions in the module such as brightRed. You may also use Word8 literals, like this. You need to specify the type as it can't be inferred:

 import Data.Word (Word8)
 putChunkLn $ Pink on 256-color terminal only
                 (201 :: Word8)

If mappend multiple chunks that change the same property, the rightmost one "wins":

 putChunkLn $ This will be blue  red  blue

This property comes in handy if you want to specify a default color for 8- and 256-color terminals, then a more specific shade for a 256-color terminal:

 putChunkLn $ Red on 8-color, pink on 256-color
                 red  (201 :: Word8)

However, if you use mappend to add additional Chunks that have text, the text will be appended:

 putChunkLn $ green  You will see this text 
               and this text too, but it will all be blue
               blue

Although one chunk can have different colors on 8- and 256-color terminals, it cannot have different colors on the same terminal. That is, if you want to print some text in one color and some text in another color, make two chunks.

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

:: 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 and a handle. If the handle is not a terminal, Dumb is returned. Otherwise, the terminal is obtained from the environment.

Changed in version 0.12.0.0 - the type of this function was different in previous versions.

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.

The text is held as a list of strict Text.

Constructors

Chunk 

Fields

textSpec :: TextSpec
 
text :: [Text]
 

fromText :: Text -> ChunkSource

Creates a Chunk from a strict Text with default colors and no special effects.

fromLazyText :: Text -> ChunkSource

Creates a Chunk from a lazy Text with default colors and no special effects.

Printing chunks

putChunks :: 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.

hPutChunks :: 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 putChunks for notes on how many colors are used.

Printing one chunk at a time

These functions make it easy to print one chunk at a time. Each function initializes the terminal once for each chunk, unlike the list-oriented functions, which only initialize the terminal once. (Initialization does not clear the screen; rather, it is a process that the terminfo library requires.) Thus there might be a performance penalty for using these functions to print large numbers of chunks. Or, there might not be--I have not benchmarked them.

These functions use the default terminal, obtained using termFromEnv.

putChunk :: Chunk -> IO ()Source

Print one chunk at a time, to standard output

putChunkLn :: Chunk -> IO ()Source

Print one chunk at a time, to standard output, append a newline

hPutChunk :: Handle -> Chunk -> IO ()Source

Print one chunk at a time, to a handle

hPutChunkLn :: Handle -> Chunk -> IO ()Source

Print one chunk at a time, to a handle, append a newline

Effects for both 8 and 256 color terminals

These Chunks affect both 8 and 256 color terminals:

 putChunkLn $ bold on 8 and 256 color terminals  bold

There are also Chunks 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 Chunks are here if you need them.

bold :: ChunkSource

Bold. What actually happens when you use Bold is going to depend on your terminal. For example, xterm allows you actually use a bold font for bold, if you have one. Otherwise, it might simulate bold by using overstriking. Another possibility is that your terminal might use a different color to indicate bold. For more details (at least for xterm), look at xterm (1) and search for boldColors.

If your terminal uses a different color for bold, this allows an 8-color terminal to really have 16 colors.

Effects for 8-color terminals only

These Chunks affect 8-color terminals only.

 putChunkLn $ Bold on 8 color terminal only  bold8

Effects for 256-color terminals only

Colors

Changing the foreground and background color

class Color a whereSource

Changing colors. Instances of this class affect the background or the foreground color. For example, to get a Chunk that changes the background to red, use back red; for the foreground, use fore red. Whether 8-color or 256-color terminals (or both) are affected depends on the particular instance.

Because Word8 is an instance of Color, you can use literals to affect the color of 256-color terminals. For example, if you have a 256 color terminal:

 putChunkLn $ "muddy yellow background" <> back (100 :: Word8)

This example would not affect an 8-color terminal, as the Word8 instance affects 256-color terminals only.

Methods

back :: a -> ChunkSource

Create a Chunk that affects the background color only.

fore :: a -> ChunkSource

Create a Chunk that affects the foreground color only.

Instances

Color Word8

Affects the foreground and background of 256-color terminals.

Color Color256 
Color Color8 
Color Enum8

Affects the foreground and background of 8-color terminals.

Color Both

Affects the foreground and background of both 8- and 256-color terminals.

Colors for both 8- and 256-color terminals

data Both Source

Things of type Both affect both 8- and 256-color terminals. (They do not affect both the foreground and background.)

Instances

Eq Both 
Ord Both 
Show Both 
Color Both

Affects the foreground and background of both 8- and 256-color terminals.

Colors for 8-color terminals

data Enum8 Source

A simple enumeration for eight values.

Constructors

E0 
E1 
E2 
E3 
E4 
E5 
E6 
E7 

Instances

Bounded Enum8 
Enum Enum8 
Eq Enum8 
Ord Enum8 
Show Enum8 
Color Enum8

Affects the foreground and background of 8-color terminals.

newtype Color8 Source

Color for an 8-color terminal. Does not affect 256-color terminals.

Constructors

Color8 

Fields

unColor8 :: Maybe Enum8

Nothing indicates to use the default color for the terminal; otherwise, use the corresponding Terminfo Color.

noColor8 :: Color8Source

Resets the color (foreground or background, as appropriate) to the default for your terminal. Usually you will not need this, as each Chunk starts out with the terminal's default colors.

Colors for 256-color terminals

newtype Color256 Source

Color for an 256-color terminal. Does not affect 8-color terminals.

Constructors

Color256 

Fields

unColor256 :: Maybe Word8

Nothing indicates to use the default color for the terminal; otherwise, use the corresponding Terminfo Color.

noColor256 :: Color256Source

Resets the color (foreground or background, as appropriate) to the default for your terminal. Usually you will not need this, as each Chunk starts out with the terminal's default colors.

to256 :: Color8 -> Color256Source

Any color for an 8-color terminal can also be used in a 256-color terminal.