table-layout-1.0.0.0: Format tabular data as grid or table.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.Layout.Table

Description

This module provides tools to layout text as grid or table. Besides basic things like specifying column positioning, alignment on the same character and length restriction it also provides advanced features like justifying text and fancy tables with styling support.

Synopsis

Column Layout

Specify how a column is rendered with the combinators in this section. Sensible default values are provided with def.

Columns

data ColSpec Source #

Specifies the layout of a column.

Instances

Instances details
Default ColSpec Source # 
Instance details

Defined in Text.Layout.Table.Spec.ColSpec

Methods

def :: ColSpec

column :: LenSpec -> Position H -> AlignSpec -> CutMark -> ColSpec Source #

Smart constructor to specify a column.

numCol :: ColSpec Source #

Numbers are positioned on the right and aligned on the floating point dot.

fixedCol :: Int -> Position H -> ColSpec Source #

Fixes the column length and positions according to the given Position.

fixedLeftCol :: Int -> ColSpec Source #

Fixes the column length and positions on the left.

defColSpec :: ColSpec Source #

The default ColSpec uses as much space as needed, positioned at the left/top (depending on orientation), does not align to any character, and uses a single unicode ellipsis on either side as a cut mark.

Length of Columns

data LenSpec Source #

Determines how long a column will be.

Instances

Instances details
Default LenSpec Source #

The default LenSpec allows columns to use as much space as needed.

Instance details

Defined in Text.Layout.Table.Spec.LenSpec

Methods

def :: LenSpec

expand :: LenSpec Source #

Allows columns to use as much space as needed.

fixed :: Int -> LenSpec Source #

Fixes column length to a specific width.

expandUntil :: Int -> LenSpec Source #

The column will expand as long as it is smaller as the given width.

fixedUntil :: Int -> LenSpec Source #

The column will be at least as wide as the given width.

expandBetween :: Int -> Int -> LenSpec Source #

The column will be at least as wide as the first width, and will expand as long as it is smaller than the second.

Positional Alignment

data Position orientation Source #

Specifies a position relative from a beginning.

Instances

Instances details
Show (Position H) Source # 
Instance details

Defined in Text.Layout.Table.Spec.Position

Methods

showsPrec :: Int -> Position H -> ShowS

show :: Position H -> String

showList :: [Position H] -> ShowS

Show (Position V) Source # 
Instance details

Defined in Text.Layout.Table.Spec.Position

Methods

showsPrec :: Int -> Position V -> ShowS

show :: Position V -> String

showList :: [Position V] -> ShowS

Default (Position orientation) Source #

The default Position displays at the left or top, depending on the orientation.

Instance details

Defined in Text.Layout.Table.Spec.Position

Methods

def :: Position orientation

Eq (Position orientation) Source # 
Instance details

Defined in Text.Layout.Table.Spec.Position

Methods

(==) :: Position orientation -> Position orientation -> Bool

(/=) :: Position orientation -> Position orientation -> Bool

data H Source #

Horizontal orientation.

Instances

Instances details
Show (Position H) Source # 
Instance details

Defined in Text.Layout.Table.Spec.Position

Methods

showsPrec :: Int -> Position H -> ShowS

show :: Position H -> String

showList :: [Position H] -> ShowS

center :: Position orientation Source #

beginning :: Position orientation Source #

Displays at the left or top, depending on the orientation.

Alignment of Cells at Characters

data AlignSpec Source #

Determines whether a column will align at a specific letter.

Instances

Instances details
Default AlignSpec Source #

No alignment is the default.

Instance details

Defined in Text.Layout.Table.Spec.AlignSpec

Methods

def :: AlignSpec

noAlign :: AlignSpec Source #

Do not align text.

charAlign :: Char -> AlignSpec Source #

Align text at the first occurence of a given Char.

predAlign :: (Char -> Bool) -> AlignSpec Source #

Align text at the first match of a predicate.

dotAlign :: AlignSpec Source #

Align all text at the first dot from the left. This is most useful for floating point numbers.

Cut Marks

data CutMark Source #

Specifies a cut mark that is used whenever content is cut to fit into a cell. If the cut mark itself is too small to fit into a cell it may be cut as well.

Instances

Instances details
Show CutMark Source # 
Instance details

Defined in Text.Layout.Table.Spec.CutMark

Methods

showsPrec :: Int -> CutMark -> ShowS

show :: CutMark -> String

showList :: [CutMark] -> ShowS

Default CutMark Source #

A single ellipsis unicode character is used to show cut marks.

Instance details

Defined in Text.Layout.Table.Spec.CutMark

Methods

def :: CutMark

Eq CutMark Source # 
Instance details

Defined in Text.Layout.Table.Spec.CutMark

Methods

(==) :: CutMark -> CutMark -> Bool

(/=) :: CutMark -> CutMark -> Bool

noCutMark :: CutMark Source #

Do not show any cut mark when content is cut.

singleCutMark :: String -> CutMark Source #

Use the cut mark on both sides by reversing it on the other.

doubleCutMark :: String -> String -> CutMark Source #

Specify two different cut marks, one for cuts on the left and one for cuts on the right.

ellipsisCutMark :: CutMark Source #

The default CutMark is a single ellipsis unicode character on each side.

Grids

Rendering

type Row a = [a] Source #

An alias for lists, conceptually for values with a horizontal arrangement.

grid :: Cell a => [ColSpec] -> [Row a] -> [Row String] Source #

A version of gridB specialized to String.

gridB :: (Cell a, StringBuilder b) => [ColSpec] -> [Row a] -> [Row b] Source #

Modifies cells according to the column specification.

gridBWithCMIs :: (Cell a, StringBuilder b) => [ColSpec] -> [Row a] -> ([Row b], [ColModInfo]) Source #

Modifies cells according to the column specification, also returning the ColModInfo used to generate the grid.

gridLines :: Cell a => [ColSpec] -> [Row a] -> [String] Source #

A version of gridLinesB specialized to String.

gridLinesB :: (Cell a, StringBuilder b) => [ColSpec] -> [Row a] -> [b] Source #

A version of gridB that joins the cells of a row with one space.

gridString :: Cell a => [ColSpec] -> [Row a] -> String Source #

A version of gridStringB specialized to String.

gridStringB :: (Cell a, StringBuilder b) => [ColSpec] -> [Row a] -> b Source #

A version of gridLinesB that also concatenates the lines.

Concatenating

concatRow :: StringBuilder b => Int -> Row b -> b Source #

Concatenates a row with a given amount of spaces.

concatGrid :: StringBuilder b => Int -> [Row b] -> b Source #

Concatenates a whole grid with the given amount of horizontal spaces between columns.

Modification Functions

altLines :: [a -> b] -> [a] -> [b] Source #

Applies functions to given lines in a alternating fashion. This makes it easy to color lines to improve readability in a row.

checkeredCells :: (a -> b) -> (a -> b) -> [[a]] -> [[b]] Source #

Applies functions to cells in a alternating fashion for every line, every other line gets shifted by one. This is useful for distinguishability of single cells in a grid arrangement.

Tables

Grouping Rows

Rows in character-based tables are separated by separator lines. This section provides the tools to decide when this separation is happening. Thus, several text rows may be in the same row of the table.

data RowGroup a Source #

Groups rows together which should not be visually seperated from each other.

rowsG :: [Row a] -> RowGroup a Source #

Group the given rows together.

rowG :: Row a -> RowGroup a Source #

Make a group of a single row.

Columns as Row Groups

Text justification may be used to turn text into length-limited columns. Such columns may be turned into a RowGroup with colsG or colsAllG.

colsG :: [Position V] -> [Col a] -> RowGroup a Source #

Create a RowGroup by aligning the columns vertically. The position is specified for each column.

colsAllG :: Position V -> [Col a] -> RowGroup a Source #

Create a RowGroup by aligning the columns vertically. Each column uses the same position.

Specifying Tables

The most basic TableSpec may be constructed by using simpleTableS.

Rendering

Render a TableSpec.

tableLines :: (Cell a, Cell r, Cell c) => TableSpec rowSep colSep r c a -> [String] Source #

A version of tableLinesB specialized to String.

tableLinesB :: (Cell a, Cell r, Cell c, StringBuilder b) => TableSpec rowSep colSep r c a -> [b] Source #

Renders a table as StringBuilder lines. Note that providing fewer layout specifications than columns or vice versa will result in not showing the redundant ones.

tableLinesBWithCMIs :: forall rowSep r colSep c a b. (Cell a, Cell r, Cell c, StringBuilder b) => TableSpec rowSep colSep r c a -> ([b], [ColModInfo]) Source #

Renders a table as StringBuilder lines, providing the ColModInfo for each column. Note that providing fewer layout specifications than columns or vice versa will result in not showing the redundant ones.

tableString :: (Cell a, Cell r, Cell c) => TableSpec rowSep colSep r c a -> String Source #

A version of tableStringB specialized to String.

tableStringB :: (Cell a, Cell r, Cell c, StringBuilder b) => TableSpec rowSep colSep r c a -> b Source #

A version of tableLinesB that also concatenates the lines.

Headers

data HeaderColSpec Source #

Specifies how a header is rendered.

Instances

Instances details
Default HeaderColSpec Source #

Header columns are usually centered.

Instance details

Defined in Text.Layout.Table.Spec.HeaderColSpec

Methods

def :: HeaderColSpec

headerColumn :: Position H -> Maybe CutMark -> HeaderColSpec Source #

Smart constructor for HeaderColSpec. By omitting the cut mark, it will use the one specified in the ColSpec like the other cells in that column.

data HeaderSpec sep a Source #

Specifies a header.

Instances

Instances details
Bifunctor HeaderSpec Source # 
Instance details

Defined in Text.Layout.Table.Spec.HeaderSpec

Methods

bimap :: (a -> b) -> (c -> d) -> HeaderSpec a c -> HeaderSpec b d

first :: (a -> b) -> HeaderSpec a c -> HeaderSpec b c

second :: (b -> c) -> HeaderSpec a b -> HeaderSpec a c

Foldable (HeaderSpec sep) Source # 
Instance details

Defined in Text.Layout.Table.Spec.HeaderSpec

Methods

fold :: Monoid m => HeaderSpec sep m -> m

foldMap :: Monoid m => (a -> m) -> HeaderSpec sep a -> m

foldMap' :: Monoid m => (a -> m) -> HeaderSpec sep a -> m

foldr :: (a -> b -> b) -> b -> HeaderSpec sep a -> b

foldr' :: (a -> b -> b) -> b -> HeaderSpec sep a -> b

foldl :: (b -> a -> b) -> b -> HeaderSpec sep a -> b

foldl' :: (b -> a -> b) -> b -> HeaderSpec sep a -> b

foldr1 :: (a -> a -> a) -> HeaderSpec sep a -> a

foldl1 :: (a -> a -> a) -> HeaderSpec sep a -> a

toList :: HeaderSpec sep a -> [a]

null :: HeaderSpec sep a -> Bool

length :: HeaderSpec sep a -> Int

elem :: Eq a => a -> HeaderSpec sep a -> Bool

maximum :: Ord a => HeaderSpec sep a -> a

minimum :: Ord a => HeaderSpec sep a -> a

sum :: Num a => HeaderSpec sep a -> a

product :: Num a => HeaderSpec sep a -> a

Traversable (HeaderSpec sep) Source # 
Instance details

Defined in Text.Layout.Table.Spec.HeaderSpec

Methods

traverse :: Applicative f => (a -> f b) -> HeaderSpec sep a -> f (HeaderSpec sep b)

sequenceA :: Applicative f => HeaderSpec sep (f a) -> f (HeaderSpec sep a)

mapM :: Monad m => (a -> m b) -> HeaderSpec sep a -> m (HeaderSpec sep b)

sequence :: Monad m => HeaderSpec sep (m a) -> m (HeaderSpec sep a)

Functor (HeaderSpec sep) Source # 
Instance details

Defined in Text.Layout.Table.Spec.HeaderSpec

Methods

fmap :: (a -> b) -> HeaderSpec sep a -> HeaderSpec sep b

(<$) :: a -> HeaderSpec sep b -> HeaderSpec sep a

Default sep => Default (HeaderSpec sep a) Source #

By the default the header is not shown.

Instance details

Defined in Text.Layout.Table.Spec.HeaderSpec

Methods

def :: HeaderSpec sep a

noneSepH :: sep -> HeaderSpec sep String Source #

Specify no header, with columns separated by a given separator.

noneH :: Default sep => HeaderSpec sep String Source #

Specify no header, with columns separated by a default separator.

fullSepH :: sep -> [HeaderColSpec] -> [a] -> HeaderSpec sep a Source #

Specify every header column in detail and separate them by the given separator.

fullH :: Default sep => [HeaderColSpec] -> [a] -> HeaderSpec sep a Source #

Specify every header column in detail and separate them with the default separator.

titlesH :: Default sep => [a] -> HeaderSpec sep a Source #

Use titles with the default header column specification and separator.

groupH :: sep -> [HeaderSpec sep a] -> HeaderSpec sep a Source #

Combine the header specification for multiple columns by separating the columns with a specific separator.

headerH :: HeaderColSpec -> a -> HeaderSpec sep a Source #

Specify the header for a single column.

defHeaderColSpec :: HeaderColSpec Source #

The default HeaderColSpec centers the text and uses no CutMark.

Styles

Multi-Row Cell Rendering

Text Justification

Split text and turn it into a column. Such columns may be combined with other columns.

justify :: Int -> [String] -> [String] Source #

Fits as many words on a line as possible depending on the given width. Every line, except the last one, gets equally filled with spaces between the words as far as possible.

justifyText :: Int -> String -> [String] Source #

Uses words to split the text into words and justifies it with justify.

>>> justifyText 10 "This text will not fit on one line."
["This  text","will   not","fit on one","line."]

Vertical Column Positioning

Turn rows of columns into a grid by aligning the columns.

data V Source #

Vertical orientation.

Instances

Instances details
Show (Position V) Source # 
Instance details

Defined in Text.Layout.Table.Spec.Position

Methods

showsPrec :: Int -> Position V -> ShowS

show :: Position V -> String

showList :: [Position V] -> ShowS

type Col a = [a] Source #

An alias for lists, conceptually for values with a vertical arrangement.

colsAsRowsAll :: Position V -> [Col a] -> [Row (Maybe a)] Source #

Merges multiple columns together to a valid grid without holes. For example:

>>> colsAsRowsAll top [justifyText 10 "This text will not fit on one line.", ["42", "23"]]
[[Just "This  text",Just "42"],[Just "will   not",Just "23"],[Just "fit on one",Nothing],[Just "line.",Nothing]]

The result is intended to be used with a grid layout function like grid.

colsAsRows :: [Position V] -> [Col a] -> [Row (Maybe a)] Source #

Works like colsAsRowsAll but every position can be specified on its own:

>>> colsAsRows [top, center, bottom] [["a1"], ["b1", "b2", "b3"], ["c3"]]
[[Just "a1",Just "b1",Nothing],[Nothing,Just "b2",Nothing],[Nothing,Just "b3",Just "c3"]]

Custom Layout Generation

Column Modification Functions

pad :: Cell a => Position o -> Int -> a -> CellMod a Source #

Pads the given cell accordingly using the position specification.

>>> buildCellMod noCutMark $ pad left 10 "foo" :: String
"foo       "

trim :: Cell a => Position o -> CutMark -> Int -> a -> CellMod a Source #

Trim a cell based on the position. Cut marks may be trimmed if necessary.

trimOrPad :: Cell a => Position o -> CutMark -> Int -> a -> CellMod a Source #

If the given text is too long, the String will be shortened according to the position specification. Adds cut marks to indicate that the column has been trimmed in length, otherwise it behaves like pad.

>>> let cm = singleCutMark ".."
>>> buildCellMod cm $ trimOrPad left cm 10 "A longer text." :: String
"A longer.."

trimOrPadBetween Source #

Arguments

:: Cell a 
=> Position o 
-> CutMark 
-> Int

The length lower to pad to if too short

-> Int

The length upper to trim to if too long

-> a 
-> CellMod a 

If the given text is too long, it will be trimmed to length upper according to the position specification, and cut marks will be added to indicate that the column has been trimmed in length. Otherwise, if the given text is too short, it will be padded to length lower.

>>> let cm = singleCutMark ".."
>>> buildCellMod cm $ trimOrPadBetween left cm 7 10 "A longer text." :: String
"A longer.."
>>> buildCellMod cm $ trimOrPadBetween left cm 7 10 "Short" :: String
"Short  "
>>> buildCellMod cm $ trimOrPadBetween left cm 7 10 "A medium" :: String
"A medium"

Preconditions that are required to be met (otherwise the output will be counterintuitive):

lower <= upper

align :: Cell a => OccSpec -> AlignInfo -> a -> CellMod a Source #

Align a cell by first locating the position to align with and then padding on both sides. If no such position is found, it will align it such that it gets aligned before that position.

>>> let { os = predOccSpec (== '.') ; ai = deriveAlignInfo os "iiii.fff" }
>>> in buildCellMod noCutMark . align os ai <$> ["1.5", "30", ".25"] :: [String]
["   1.5  ","  30    ","    .25 "]

This function assumes that the given String fits the AlignInfo. Thus:

ai <> deriveAlignInfo s = ai

alignFixed :: Cell a => Position o -> CutMark -> Int -> OccSpec -> AlignInfo -> a -> CellMod a Source #

Aligns a cell using a fixed width, fitting it to the width by either filling or cutting while respecting the alignment.

buildCellMod :: (Cell c, StringBuilder s) => CutMark -> CellMod c -> s Source #

Interpret CellMod to create a builder.

adjustCell :: Int -> Int -> a -> CellView a Source #

Add an adjustment to the left and right of a Cell. Positive numbers are padding and negative numbers are trimming.

Column Modifaction Primitives

These functions are provided to be reused. For example if someone wants to render their own kind of tables.

data ColModInfo Source #

Specifies how a column should be modified. Values of this type are derived in a traversal over the input columns by using deriveColModInfosFromGrid. Finally, columnModifier will interpret them and apply the appropriate modification function to the cells of the column.

widthCMI :: ColModInfo -> Int Source #

Get the exact width of a ColModInfo after applying it with columnModifier.

unalignedCMI :: ColModInfo -> ColModInfo Source #

Remove alignment from a ColModInfo. This is used to change alignment of headers while using the combined width information.

ensureWidthCMI :: Int -> Position H -> ColModInfo -> ColModInfo Source #

Ensures that the modification provides a minimum width but only if it is not limited.

ensureWidthOfCMI :: Cell a => a -> Position H -> ColModInfo -> ColModInfo Source #

Ensures that the given String will fit into the modified columns.

columnModifier :: (Cell a, StringBuilder b) => Position H -> CutMark -> ColModInfo -> a -> b Source #

Generates a function which modifies a given cell according to Position, CutMark and ColModInfo. This is used to modify a single cell of a column to bring all cells of a column to the same width.

data AlignInfo Source #

Specifies the length before and after an alignment position (excluding the alignment character).

Instances

Instances details
Monoid AlignInfo Source # 
Instance details

Defined in Text.Layout.Table.Primitives.AlignInfo

Semigroup AlignInfo Source #

Produce an AlignInfo that is wide enough to hold inputs of both given AlignInfos.

Instance details

Defined in Text.Layout.Table.Primitives.AlignInfo

Methods

(<>) :: AlignInfo -> AlignInfo -> AlignInfo

sconcat :: NonEmpty AlignInfo -> AlignInfo

stimes :: Integral b => b -> AlignInfo -> AlignInfo

Show AlignInfo Source # 
Instance details

Defined in Text.Layout.Table.Primitives.AlignInfo

Methods

showsPrec :: Int -> AlignInfo -> ShowS

show :: AlignInfo -> String

showList :: [AlignInfo] -> ShowS

Eq AlignInfo Source # 
Instance details

Defined in Text.Layout.Table.Primitives.AlignInfo

Methods

(==) :: AlignInfo -> AlignInfo -> Bool

(/=) :: AlignInfo -> AlignInfo -> Bool

widthAI :: AlignInfo -> Int Source #

The column width when using the AlignInfo.

deriveColModInfosFromGrid :: Cell a => [ColSpec] -> [Row a] -> [ColModInfo] Source #

Derive the ColModInfo for each column of a list of rows by using the corresponding ColSpec.

deriveColModInfosFromColumns :: (Foldable col, Cell a) => [ColSpec] -> [col a] -> [ColModInfo] Source #

Derive the ColModInfo for each column of a list of columns by using the corresponding ColSpec.

deriveAlignInfo :: Cell a => OccSpec -> a -> AlignInfo Source #

Generate the AlignInfo of a cell by using the OccSpec.

data OccSpec Source #

Specifies an occurence of a letter.

Table Headers

zipHeader :: b -> [b] -> HeaderSpec sep a -> HeaderSpec sep (b, a) Source #

Zip a HeaderSpec with a list.

flattenHeader :: HeaderSpec sep a -> [Either sep a] Source #

Flatten a header to produce a list of content and separators.

headerContents :: HeaderSpec sep a -> [(HeaderColSpec, a)] Source #

Get the titles and column specifications from a header.