rainbox-0.24.4.0: Two-dimensional box pretty printing, with colors

Safe HaskellNone
LanguageHaskell2010

Rainbox

Contents

Description

Typically to use Rainbox you will want these imports:

import qualified Data.Sequence as Seq
import Rainbow
import Rainbox

-- and, for GHC before 7.10:
import Data.Monoid

Rainbox does not re-export anything from Data.Sequence or Rainbow because I don't know if you want all those things dumped into the same namespace.

Rainbox.Tutorial wil get you started. Rainbox.Core contains the implementation details, which you should not need to pay attention to (if you do need to use Rainbox.Core for ordinary usage of the library, that's a bug; please report it.)

Synopsis

Alignment and Boxes

data Alignment a Source #

Alignment. Used in conjunction with Horizontal and Vertical, this determines how a payload aligns with the axis of a Box.

Instances
Functor Alignment Source # 
Instance details

Defined in Rainbox.Core

Methods

fmap :: (a -> b) -> Alignment a -> Alignment b #

(<$) :: a -> Alignment b -> Alignment a #

Foldable Alignment Source # 
Instance details

Defined in Rainbox.Core

Methods

fold :: Monoid m => Alignment m -> m #

foldMap :: Monoid m => (a -> m) -> Alignment a -> m #

foldr :: (a -> b -> b) -> b -> Alignment a -> b #

foldr' :: (a -> b -> b) -> b -> Alignment a -> b #

foldl :: (b -> a -> b) -> b -> Alignment a -> b #

foldl' :: (b -> a -> b) -> b -> Alignment a -> b #

foldr1 :: (a -> a -> a) -> Alignment a -> a #

foldl1 :: (a -> a -> a) -> Alignment a -> a #

toList :: Alignment a -> [a] #

null :: Alignment a -> Bool #

length :: Alignment a -> Int #

elem :: Eq a => a -> Alignment a -> Bool #

maximum :: Ord a => Alignment a -> a #

minimum :: Ord a => Alignment a -> a #

sum :: Num a => Alignment a -> a #

product :: Num a => Alignment a -> a #

Traversable Alignment Source # 
Instance details

Defined in Rainbox.Core

Methods

traverse :: Applicative f => (a -> f b) -> Alignment a -> f (Alignment b) #

sequenceA :: Applicative f => Alignment (f a) -> f (Alignment a) #

mapM :: Monad m => (a -> m b) -> Alignment a -> m (Alignment b) #

sequence :: Monad m => Alignment (m a) -> m (Alignment a) #

Eq a => Eq (Alignment a) Source # 
Instance details

Defined in Rainbox.Core

Methods

(==) :: Alignment a -> Alignment a -> Bool #

(/=) :: Alignment a -> Alignment a -> Bool #

Ord a => Ord (Alignment a) Source # 
Instance details

Defined in Rainbox.Core

Show a => Show (Alignment a) Source # 
Instance details

Defined in Rainbox.Core

Semigroup (Alignment a) Source # 
Instance details

Defined in Rainbox.Core

Methods

(<>) :: Alignment a -> Alignment a -> Alignment a #

sconcat :: NonEmpty (Alignment a) -> Alignment a #

stimes :: Integral b => b -> Alignment a -> Alignment a #

Monoid (Alignment a) Source #

mempty is center. mappend takes the rightmost non-center value.

Instance details

Defined in Rainbox.Core

data Horizontal Source #

Determines how a payload aligns with a horizontal axis.

Instances
Eq Horizontal Source # 
Instance details

Defined in Rainbox.Core

Ord Horizontal Source # 
Instance details

Defined in Rainbox.Core

Show Horizontal Source # 
Instance details

Defined in Rainbox.Core

Orientation Horizontal Source # 
Instance details

Defined in Rainbox.Core

UpDown (Box Horizontal) Source # 
Instance details

Defined in Rainbox.Core

UpDown (Payload Horizontal) Source # 
Instance details

Defined in Rainbox.Core

HasWidth (Box Horizontal) Source # 
Instance details

Defined in Rainbox.Core

HasHeight (Box Horizontal) Source # 
Instance details

Defined in Rainbox.Core

data Vertical Source #

Determines how a payload aligns with a vertical axis.

Instances
Eq Vertical Source # 
Instance details

Defined in Rainbox.Core

Ord Vertical Source # 
Instance details

Defined in Rainbox.Core

Show Vertical Source # 
Instance details

Defined in Rainbox.Core

Orientation Vertical Source # 
Instance details

Defined in Rainbox.Core

LeftRight (Box Vertical) Source # 
Instance details

Defined in Rainbox.Core

LeftRight (Payload Vertical) Source # 
Instance details

Defined in Rainbox.Core

HasWidth (Box Vertical) Source # 
Instance details

Defined in Rainbox.Core

Methods

width :: Box Vertical -> Int Source #

HasHeight (Box Vertical) Source # 
Instance details

Defined in Rainbox.Core

Methods

height :: Box Vertical -> Int Source #

center :: Alignment a Source #

Place this payload so that it is centered on the vertical axis or horizontal axis.

left :: Alignment Vertical Source #

Place this payload's left edge on the vertical axis.

right :: Alignment Vertical Source #

Place this payload's right edge on the vertical axis.

top :: Alignment Horizontal Source #

Place this payload's top edge on the horizontal axis.

bottom :: Alignment Horizontal Source #

Place this payload's bottom edge on the horizontal axis.

centerH :: Alignment Horizontal Source #

Center horizontally; like center, but monomorphic.

centerV :: Alignment Vertical Source #

Center vertically; like center, but monomorphic.

data Box a Source #

A Box is the central building block. It consists of zero or more payloads; each payload has the same orientation, which is either Horizontal or Vertical. This orientation also determines the orientation of the entire Box.

A Box is a Monoid so you can combine them using the usual monoid functions. For a Box Vertical, the leftmost values added with mappend are at the top of the Box; for a Box Horizontal, the leftmost values added with mappend are on the left side of the Box.

Instances
Eq a => Eq (Box a) Source # 
Instance details

Defined in Rainbox.Core

Methods

(==) :: Box a -> Box a -> Bool #

(/=) :: Box a -> Box a -> Bool #

Ord a => Ord (Box a) Source # 
Instance details

Defined in Rainbox.Core

Methods

compare :: Box a -> Box a -> Ordering #

(<) :: Box a -> Box a -> Bool #

(<=) :: Box a -> Box a -> Bool #

(>) :: Box a -> Box a -> Bool #

(>=) :: Box a -> Box a -> Bool #

max :: Box a -> Box a -> Box a #

min :: Box a -> Box a -> Box a #

Show a => Show (Box a) Source # 
Instance details

Defined in Rainbox.Core

Methods

showsPrec :: Int -> Box a -> ShowS #

show :: Box a -> String #

showList :: [Box a] -> ShowS #

Semigroup (Box a) Source # 
Instance details

Defined in Rainbox.Core

Methods

(<>) :: Box a -> Box a -> Box a #

sconcat :: NonEmpty (Box a) -> Box a #

stimes :: Integral b => b -> Box a -> Box a #

Monoid (Box a) Source # 
Instance details

Defined in Rainbox.Core

Methods

mempty :: Box a #

mappend :: Box a -> Box a -> Box a #

mconcat :: [Box a] -> Box a #

UpDown (Box Horizontal) Source # 
Instance details

Defined in Rainbox.Core

LeftRight (Box Vertical) Source # 
Instance details

Defined in Rainbox.Core

HasWidth (Box Vertical) Source # 
Instance details

Defined in Rainbox.Core

Methods

width :: Box Vertical -> Int Source #

HasWidth (Box Horizontal) Source # 
Instance details

Defined in Rainbox.Core

HasHeight (Box Vertical) Source # 
Instance details

Defined in Rainbox.Core

Methods

height :: Box Vertical -> Int Source #

HasHeight (Box Horizontal) Source # 
Instance details

Defined in Rainbox.Core

class Orientation a where Source #

This typeclass is responsible for transforming a Box into Rainbow Chunk so they can be printed to your screen. This requires adding appropriate whitespace with the right colors, as well as adding newlines in the right places.

Minimal complete definition

rodRows, spacer, spreader

Methods

spacer :: Radiant -> Int -> Box a Source #

Builds a one-dimensional box of the given size; its single dimension is parallel to the axis. When added to a box, it will insert blank space of the given length. For a Box Horizontal, this produces a horizontal line; for a Box Vertical, a vertical line.

spreader :: Alignment a -> Int -> Box a Source #

Builds a one-dimensional box of the given size; its single dimension is perpendicular to the axis. This can be used to make a Box Vertical wider or a Box Horizontal taller.

Box construction

fromChunk Source #

Arguments

:: Alignment a 
-> Radiant

Background color. The background color in the Chunk is not changed; this background is used if the Payload must be padded later on.

-> Chunk 
-> Box a 

Construct a box from a single Chunk.

blank Source #

Arguments

:: Alignment a 
-> Radiant

Color for the blank area.

-> Height 
-> Width 
-> Box a 

Construct a blank box. Useful for adding in background spacers. For functions that build one-dimensional boxes, see spacer and spreader.

wrap Source #

Arguments

:: Orientation a 
=> Alignment b

Alignment for new Box. This also determines whether the new Box is Horizontal or Vertical.

-> Radiant

Background color for new box

-> Box a 
-> Box b 

Wrap a Box in another Box. Useful for changing a Horizontal Box to a Vertical one, or simply for putting a Box inside another one to control size and background color.

Rendering

render :: Orientation a => Box a -> Seq Chunk Source #

Convert a box to a Seq of Chunk in preparation for rendering. Use toList to convert the Seq of Chunk to a list so that you can print it using the functions in Rainbow.

putBox :: Orientation a => Box a -> IO () Source #

Uses hPutBox to render the given Box to standard output.

hPutBox :: Orientation a => Handle -> Box a -> IO () Source #

Renders a Box to the given Handle. This uses hPutChunks so consult that function for more details on how this works; generally it is going to use the maximum number of colors possible for your terminal.

Tables

Types and functions to build a simple spreadsheet-like grid. You create a nested Seq of Cell, and then use tableByRows or tableByColumns to create a Box, which you can then render using Rainbow functions. Each column is as wide as necessary to accomodate the widest cell in the column, but no wider, which means the columns will tend to meld together. To add separators you'll have to add separator cells in yourself.

Cell type

data Cell Source #

A single cell in a spreadsheet-like grid.

Constructors

Cell 

Fields

Instances
Eq Cell Source # 
Instance details

Defined in Rainbox.Core

Methods

(==) :: Cell -> Cell -> Bool #

(/=) :: Cell -> Cell -> Bool #

Ord Cell Source # 
Instance details

Defined in Rainbox.Core

Methods

compare :: Cell -> Cell -> Ordering #

(<) :: Cell -> Cell -> Bool #

(<=) :: Cell -> Cell -> Bool #

(>) :: Cell -> Cell -> Bool #

(>=) :: Cell -> Cell -> Bool #

max :: Cell -> Cell -> Cell #

min :: Cell -> Cell -> Cell #

Show Cell Source # 
Instance details

Defined in Rainbox.Core

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Semigroup Cell Source # 
Instance details

Defined in Rainbox.Core

Methods

(<>) :: Cell -> Cell -> Cell #

sconcat :: NonEmpty Cell -> Cell #

stimes :: Integral b => b -> Cell -> Cell #

Monoid Cell Source #

mappend combines two Cell horizontally so they are side-by-side, left-to-right. The _horizontal, _vertical, and _background fields are combined using their respective Monoid instances. mempty uses the respective mempty value for each field.

Instance details

Defined in Rainbox.Core

Methods

mempty :: Cell #

mappend :: Cell -> Cell -> Cell #

mconcat :: [Cell] -> Cell #

separator :: Radiant -> Int -> Cell Source #

Creates a blank Cell with the given background color and width; useful for adding separators between columns.

van Laarhoven lenses

Table builders

tableByRows :: Seq (Seq Cell) -> Box Vertical Source #

Create a table where each inner Seq is a row of cells, from left to right. If necessary, blank cells are added to the end of a row to ensure that each row has the same number of cells as the longest row.

tableByColumns :: Seq (Seq Cell) -> Box Horizontal Source #

Create a table where each inner Seq is a column of cells, from top to bottom. If necessary, blank cells are added to the end of a column to ensure that each column has the same number of cells as the longest column.

Bi-color tables

type BicolorTableCellLine = Seq Chunk Source #

A single line within a cell in a BicolorTable. For each Chunk, leave the back as the default if you want the Chunk background to match _bctEvenBackground or _bctOddBackground. If you specify a background color for any Chunk, it will for that Chunk override the table's background color.

type BicolorTableCell = Seq BicolorTableCellLine Source #

The set of all lines within a cell in a BicolorTable.

type BicolorTableRow = Seq BicolorTableCell Source #

The set of all columns in a single row. The length of each BicolorTableRow must be equal to the length of _bctAlignments; otherwise, bicolorTable will fail with an error message.

data BicolorTable Source #

Description for a table with rows of alternating background colors. For instance, if designed for a terminal with a white background, the row backgrounds might alternate between white and light grey. The different backgrounds help with readability.

For the Chunk that are in the table, simply leave the back color blank if you wish to use the row's background color. Upon rendering, bicolorTable will render the Chunk with a background color that matches that of the row. If you specify a background color for a Chunk, it will override the background color for the row.

Note that a row may contain more than one line of text.

Unlike tables built with tableByRows or tableByColumns, all tables built with bicolorTable will have separator colums between each column.

Constructors

BicolorTable 

Fields

Instances
Show BicolorTable Source # 
Instance details

Defined in Rainbox.BicolorTable

bicolorTable :: BicolorTable -> Either String (Box Vertical) Source #

Creates a bi-color table. If the number of columns in each BicolorTableRow is not equal to the length of _bctAlignments, this will return Left; otherwise, returns Right with a Box Vertical that can then be rendered.

hPutBicolorTable :: Handle -> BicolorTable -> IO () Source #

Creates a bi-color table and renders it to the given Handle using bicolorTable and hPutBox. Any errors from bicolorTable are repored with fail.

putBicolorTable :: BicolorTable -> IO () Source #

Creates a bi-color table and renders it to standard output using hPutBicolorTable.

van Laarhoven lenses