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

Safe HaskellSafe-Inferred
LanguageHaskell2010

Rainbow

Contents

Description

Rainbow handles colors and special effects for text.

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 #-}

or, in GHCi:

>>> :set -XOverloadedStrings

and all future examples assume you have enabled OverloadedStrings.

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 <> fore (to256 red8)

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:

putChunkLn $ "Pink on 256-color terminal only"
               <> fore (201 :: Word8)

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

putChunkLn $ "This will be blue" <> fore red <> fore 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"
               <> fore red <> fore (201 :: Word8)

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

putChunkLn $ fore green <> "You will see this text "
             <> "and this text too, but it will all be blue"
             <> fore 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

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.

chunkFromText :: Text -> Chunk Source

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

chunkFromTexts :: [Text] -> Chunk Source

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

chunkFromLazyText :: Text -> Chunk Source

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

chunkFromLazyTexts :: [Text] -> Chunk Source

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

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

bold :: Chunk Source

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

These Chunks affect 256-color terminals only.

putChunkLn $ "Underlined on 256-color terminal, "
             <> "bold on 8-color terminal"
             <> underline256 <> bold8

Colors

Changing the foreground and background color

class Color a where Source

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 -> Chunk Source

Create a Chunk that affects the background color only.

fore :: a -> Chunk Source

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 Radiant

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

Colors for both 8- and 256-color terminals

data Radiant Source

A Radiant affects both 8- and 256-color terminals. (It does not necessarily affect both the foreground and background; whether it affects the foreground, background, or both depends upon the context in which it is used.)

Constructors

Radiant 

Fields

rad8 :: Color8
 
rad256 :: Maybe Color256

If Nothing, use the rad8 color on 256-color terminals.

Instances

Eq Radiant 
Ord Radiant 
Show Radiant 
Generic Radiant 
Color Radiant

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

Typeable * Radiant 
type Rep Radiant 

noColorRadiant :: Radiant Source

A Radiant that uses the terminal's default colors for both 8- and 256-color terminals.

both :: Color8 -> Radiant Source

A Radiant with the same color for both 8- and 256-color terminals.

Colors for 8-color terminals only

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 
Generic Enum8 
Color Enum8

Affects the foreground and background of 8-color terminals.

Typeable * Enum8 
type Rep Enum8 

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 :: Color8 Source

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 only

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 :: Color256 Source

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 -> Color256 Source

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

Converting Chunk to ByteString

To print a Chunk, you need to convert it to some ByteStrings.

All these functions convert the Text to UTF-8 ByteStrings. Many of these functions return a difference list. Learn You a Haskell for Great Good has a great explanation of difference lists:

http://learnyouahaskell.com/for-a-few-monads-more

If you don't want to learn about difference lists, just stick with using chunksToByteStrings and use byteStringMakerFromEnvironment if you want to use the highest number of colors possible, or, to manually specify the number of colors, use chunksToByteStrings with toByteStringsColors0, toByteStringsColors8, or toByteStringsColors256 as the first argument. chunksToByteStrings has an example.

byteStringMakerFromEnvironment :: IO (Chunk -> [ByteString] -> [ByteString]) Source

Spawns a subprocess to read the output of tput colors. If this says there are at least 256 colors are available, returns toByteStringsColors256. Otherwise, if there are at least 8 colors available, returns toByteStringsColors8. Otherwise, returns toByteStringsColors0.

If any IO exceptions arise during this process, they are discarded and toByteStringsColors0 is returned.

byteStringMakerFromHandle :: Handle -> IO (Chunk -> [ByteString] -> [ByteString]) Source

Like byteStringMakerFromEnvironment but also consults a provided Handle. If the Handle is not a terminal, toByteStringsColors0 is returned. Otherwise, the value of byteStringMakerFromEnvironment is returned.

toByteStringsColors0 :: Chunk -> [ByteString] -> [ByteString] Source

Convert a Chunk to a list of ByteString; do not show any colors. When applied to a Chunk, this function returns a difference list.

toByteStringsColors8 :: Chunk -> [ByteString] -> [ByteString] Source

Convert a Chunk to a list of ByteString; show eight colors. When applied to a Chunk, this function returns a difference list.

toByteStringsColors256 :: Chunk -> [ByteString] -> [ByteString] Source

Convert a Chunk to a list of ByteString; show 256 colors. When applied to a Chunk, this function returns a difference list.

chunksToByteStrings Source

Arguments

:: (Chunk -> [ByteString] -> [ByteString])

Function that converts Chunk to ByteString. This function, when applied to a Chunk, returns a difference list.

-> [Chunk] 
-> [ByteString] 

Convert a list of Chunk to a list of ByteString. The length of the returned list may be longer than the length of the input list.

So, for example, to print a bunch of chunks to standard output using 256 colors:

{-# LANGUAGE OverloadedStrings #-}
module PrintMyChunks where

import qualified Data.ByteString as BS
import Rainbow

myChunks :: [Chunk]
myChunks = [ "Roses" <> fore red, "\n", "Violets" <> fore blue, "\n" ]

myPrintedChunks :: IO ()
myPrintedChunks = mapM_ BS.putStr
                . chunksToByteStrings toByteStringsColors256
                $ myChunks

To use the highest number of colors that this terminal supports:

myPrintedChunks' :: IO ()
myPrintedChunks' = do
  printer <- byteStringMakerFromEnvironment
  mapM_ BS.putStr
    . chunksToByteStrings printer
    $ myChunks

Quick and dirty functions for IO

For efficiency reasons you probably don't want to use these when printing large numbers of Chunk, but they are handy for throwaway uses like experimenting in GHCi.

putChunk :: Chunk -> IO () Source

Writes a Chunk to standard output. Spawns a child process to read the output of tput colors to determine how many colors to use, for every single chunk. Therefore, this is not going to win any speed awards. You are better off using chunksToByteStrings and the functions in Data.ByteString to print your Chunks if you are printing a lot of them.

putChunkLn :: Chunk -> IO () Source

Writes a Chunk to standard output, and appends a newline. Spawns a child process to read the output of tput colors to determine how many colors to use, for every single chunk. Therefore, this is not going to win any speed awards. You are better off using chunksToByteStrings and the functions in Data.ByteString to print your Chunks if you are printing a lot of them.

Re-exports

module Data.Text

module Data.Word

Notes on terminals

Earlier versions of Rainbow used the Haskell terminfo library for dealing with the terminal. Terminfo is available at

https://hackage.haskell.org/package/terminfo

Terminfo, in turn, uses the UNIX terminfo library. The biggest advantage of using Terminfo is that it is compatible with a huge variety of terminals. Many of these terminals are hardware models that are gathering dust in an IBM warehouse somewhere, but even modern software terminals might have quirks. Terminfo covers all those.

The disadvantage is that using Terminfo requires you to perform IO whenever you need to format output for the terminal. Your only choice when using Terminfo is to send output directly to the terminal, or to a handle. This goes against typical Haskell practice, where we try to write pure code whenever possible.

Perhaps surprisingly, there are times where you may want to format output, but not immediately send it to the terminal. Maybe you want to send it to a file instead, or maybe you want to use a Haskell library like Pipes and stream it somewhere. Terminfo is a binding to a Unix library that is not designed for this sort of thing. The closest you could get using Terminfo would be to make a Handle that is backed by a in-memory buffer. There is a package for that sort of thing:

http://hackage.haskell.org/package/knob

but it seems like a nasty workaround. Or you can hijack stdout and send that somewhere--again, nasty workaround.

So I decided to stop using Terminfo. That means Rainbow no longer supports a menagerie of bizarre terminals. It instead just uses the standard ISO 6429 / ECMA 48 terminal codes. These are the same codes that are used by xterm, the OS X Terminal, the Linux console, or any other reasonably modern software terminal. Realistically they are the only terminals Rainbow would be used for.

The 256 color capability is not in ISO 6429, but it is widely supported.

Probably the most common so-called terminals in use today that do NOT support the ISO 6429 codes are those that are not really terminals. For instance, you might use an Emacs shell buffer. For those situations just use toByteStringsColors0.

I also decided to standardize on UTF-8 for the Text output.. These days that seems reasonable.

Now, to figure out how many colors the terminal supports, Rainbow simply uses the tput program. This removes the dependency on Terminfo altogether.

Apparently it's difficult to get ISO 6429 support on Microsoft Windows. Oh well.