| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- data Alignment a
- data Horizontal
- data Vertical
- center :: Alignment a
- left :: Alignment Vertical
- right :: Alignment Vertical
- top :: Alignment Horizontal
- bottom :: Alignment Horizontal
- centerH :: Alignment Horizontal
- centerV :: Alignment Vertical
- data Box a
- class Orientation a where
- fromChunk :: Alignment a -> Radiant -> Chunk -> Box a
- blank :: Alignment a -> Radiant -> Height -> Width -> Box a
- wrap :: Orientation a => Alignment b -> Radiant -> Box a -> Box b
- render :: Orientation a => Box a -> Seq Chunk
- putBox :: Orientation a => Box a -> IO ()
- hPutBox :: Orientation a => Handle -> Box a -> IO ()
- data Cell = Cell {}
- separator :: Radiant -> Int -> Cell
- rows :: Lens' Cell (Seq (Seq Chunk))
- horizontal :: Lens' Cell (Alignment Horizontal)
- vertical :: Lens' Cell (Alignment Vertical)
- background :: Lens' Cell Radiant
- tableByRows :: Seq (Seq Cell) -> Box Vertical
- tableByColumns :: Seq (Seq Cell) -> Box Horizontal
Alignment and Boxes
Alignment. Used in conjunction with Horizontal and Vertical,
this determines how a payload aligns with the axis of a Box.
Instances
| Functor Alignment Source # | |
| Foldable Alignment Source # | |
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] # length :: Alignment a -> Int # elem :: Eq a => a -> Alignment a -> Bool # maximum :: Ord a => Alignment a -> a # minimum :: Ord a => Alignment a -> a # | |
| Traversable Alignment Source # | |
| Eq a => Eq (Alignment a) Source # | |
| Ord a => Ord (Alignment a) Source # | |
Defined in Rainbox.Core | |
| Show a => Show (Alignment a) Source # | |
| Semigroup (Alignment a) Source # | |
| Monoid (Alignment a) Source # |
|
data Horizontal Source #
Determines how a payload aligns with a horizontal axis.
Instances
| Eq Horizontal Source # | |
Defined in Rainbox.Core | |
| Ord Horizontal Source # | |
Defined in Rainbox.Core Methods compare :: Horizontal -> Horizontal -> Ordering # (<) :: Horizontal -> Horizontal -> Bool # (<=) :: Horizontal -> Horizontal -> Bool # (>) :: Horizontal -> Horizontal -> Bool # (>=) :: Horizontal -> Horizontal -> Bool # max :: Horizontal -> Horizontal -> Horizontal # min :: Horizontal -> Horizontal -> Horizontal # | |
| Show Horizontal Source # | |
Defined in Rainbox.Core Methods showsPrec :: Int -> Horizontal -> ShowS # show :: Horizontal -> String # showList :: [Horizontal] -> ShowS # | |
| Orientation Horizontal Source # | |
Defined in Rainbox.Core | |
| UpDown (Box Horizontal) Source # | |
Defined in Rainbox.Core | |
| UpDown (Payload Horizontal) Source # | |
Defined in Rainbox.Core | |
| HasWidth (Box Horizontal) Source # | |
Defined in Rainbox.Core | |
| HasHeight (Box Horizontal) Source # | |
Defined in Rainbox.Core | |
Determines how a payload aligns with a vertical axis.
center :: Alignment a Source #
Place this payload so that it is centered on the vertical axis or horizontal 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.
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 # | |
| Ord a => Ord (Box a) Source # | |
| Show a => Show (Box a) Source # | |
| Semigroup (Box a) Source # | |
| Monoid (Box a) Source # | |
| UpDown (Box Horizontal) Source # | |
Defined in Rainbox.Core | |
| LeftRight (Box Vertical) Source # | |
| HasWidth (Box Vertical) Source # | |
| HasWidth (Box Horizontal) Source # | |
Defined in Rainbox.Core | |
| HasHeight (Box Vertical) Source # | |
| HasHeight (Box Horizontal) Source # | |
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.
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.
Instances
| Orientation Vertical Source # | |
| Orientation Horizontal Source # | |
Defined in Rainbox.Core | |
Box construction
Arguments
| :: Alignment a | |
| -> Radiant | Background color. The background color in the |
| -> Chunk | |
| -> Box a |
Construct a box from a single Chunk.
Arguments
| :: Orientation a | |
| => Alignment b | Alignment for new |
| -> Radiant | Background color for new box |
| -> Box a | |
| -> Box b |
Rendering
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
A single cell in a spreadsheet-like grid.
Constructors
| Cell | |
Fields
| |
Instances
| Eq Cell Source # | |
| Ord Cell Source # | |
| Show Cell Source # | |
| Semigroup Cell Source # | |
| Monoid Cell Source # |
|
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.