{-# LANGUAGE MultiWayIf #-}
-- | This module provides a table widget that can draw other widgets
-- in a table layout, draw borders between rows and columns, and allow
-- configuration of row and column alignment. To get started, see
-- 'table'.
module Brick.Widgets.Table
  (
  -- * Types
    Table
  , ColumnAlignment(..)
  , RowAlignment(..)
  , TableException(..)

  -- * Construction
  , table

  -- * Configuration
  , alignLeft
  , alignRight
  , alignCenter
  , alignTop
  , alignMiddle
  , alignBottom
  , setColAlignment
  , setRowAlignment
  , setDefaultColAlignment
  , setDefaultRowAlignment
  , surroundingBorder
  , rowBorders
  , columnBorders

  -- * Rendering
  , renderTable
  )
where

import Control.Monad (forM)
import qualified Control.Exception as E
import Data.List (transpose, intersperse, nub)
import qualified Data.Map as M
#if !(MIN_VERSION_base(4,11,0))
import Data.Monoid ((<>))
#endif
import Graphics.Vty (imageHeight, imageWidth, charFill)
import Lens.Micro ((^.))

import Brick.Types
import Brick.Widgets.Core
import Brick.Widgets.Center
import Brick.Widgets.Border

-- | Column alignment modes. Use these modes with the alignment
-- functions in this module to configure column alignment behavior.
data ColumnAlignment =
    AlignLeft
    -- ^ Align all cells to the left.
    | AlignCenter
    -- ^ Center the content horizontally in all cells in the column.
    | AlignRight
    -- ^ Align all cells to the right.
    deriving (ColumnAlignment -> ColumnAlignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnAlignment -> ColumnAlignment -> Bool
$c/= :: ColumnAlignment -> ColumnAlignment -> Bool
== :: ColumnAlignment -> ColumnAlignment -> Bool
$c== :: ColumnAlignment -> ColumnAlignment -> Bool
Eq, Int -> ColumnAlignment -> ShowS
[ColumnAlignment] -> ShowS
ColumnAlignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnAlignment] -> ShowS
$cshowList :: [ColumnAlignment] -> ShowS
show :: ColumnAlignment -> String
$cshow :: ColumnAlignment -> String
showsPrec :: Int -> ColumnAlignment -> ShowS
$cshowsPrec :: Int -> ColumnAlignment -> ShowS
Show, ReadPrec [ColumnAlignment]
ReadPrec ColumnAlignment
Int -> ReadS ColumnAlignment
ReadS [ColumnAlignment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ColumnAlignment]
$creadListPrec :: ReadPrec [ColumnAlignment]
readPrec :: ReadPrec ColumnAlignment
$creadPrec :: ReadPrec ColumnAlignment
readList :: ReadS [ColumnAlignment]
$creadList :: ReadS [ColumnAlignment]
readsPrec :: Int -> ReadS ColumnAlignment
$creadsPrec :: Int -> ReadS ColumnAlignment
Read)

-- | Row alignment modes. Use these modes with the alignment functions
-- in this module to configure row alignment behavior.
data RowAlignment =
    AlignTop
    -- ^ Align all cells to the top.
    | AlignMiddle
    -- ^ Center the content vertically in all cells in the row.
    | AlignBottom
    -- ^ Align all cells to the bottom.
    deriving (RowAlignment -> RowAlignment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowAlignment -> RowAlignment -> Bool
$c/= :: RowAlignment -> RowAlignment -> Bool
== :: RowAlignment -> RowAlignment -> Bool
$c== :: RowAlignment -> RowAlignment -> Bool
Eq, Int -> RowAlignment -> ShowS
[RowAlignment] -> ShowS
RowAlignment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowAlignment] -> ShowS
$cshowList :: [RowAlignment] -> ShowS
show :: RowAlignment -> String
$cshow :: RowAlignment -> String
showsPrec :: Int -> RowAlignment -> ShowS
$cshowsPrec :: Int -> RowAlignment -> ShowS
Show, ReadPrec [RowAlignment]
ReadPrec RowAlignment
Int -> ReadS RowAlignment
ReadS [RowAlignment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RowAlignment]
$creadListPrec :: ReadPrec [RowAlignment]
readPrec :: ReadPrec RowAlignment
$creadPrec :: ReadPrec RowAlignment
readList :: ReadS [RowAlignment]
$creadList :: ReadS [RowAlignment]
readsPrec :: Int -> ReadS RowAlignment
$creadsPrec :: Int -> ReadS RowAlignment
Read)

-- | A table creation exception.
data TableException =
    TEUnequalRowSizes
    -- ^ Rows did not all have the same number of cells.
    | TEInvalidCellSizePolicy
    -- ^ Some cells in the table did not use the 'Fixed' size policy for
    -- both horizontal and vertical sizing.
    deriving (TableException -> TableException -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableException -> TableException -> Bool
$c/= :: TableException -> TableException -> Bool
== :: TableException -> TableException -> Bool
$c== :: TableException -> TableException -> Bool
Eq, Int -> TableException -> ShowS
[TableException] -> ShowS
TableException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableException] -> ShowS
$cshowList :: [TableException] -> ShowS
show :: TableException -> String
$cshow :: TableException -> String
showsPrec :: Int -> TableException -> ShowS
$cshowsPrec :: Int -> TableException -> ShowS
Show, ReadPrec [TableException]
ReadPrec TableException
Int -> ReadS TableException
ReadS [TableException]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TableException]
$creadListPrec :: ReadPrec [TableException]
readPrec :: ReadPrec TableException
$creadPrec :: ReadPrec TableException
readList :: ReadS [TableException]
$creadList :: ReadS [TableException]
readsPrec :: Int -> ReadS TableException
$creadsPrec :: Int -> ReadS TableException
Read)

instance E.Exception TableException where

-- | A table data structure for widgets of type 'Widget' @n@. Create a
-- table with 'table'.
data Table n =
    Table { forall n. Table n -> Map Int ColumnAlignment
columnAlignments :: M.Map Int ColumnAlignment
          , forall n. Table n -> Map Int RowAlignment
rowAlignments :: M.Map Int RowAlignment
          , forall n. Table n -> [[Widget n]]
tableRows :: [[Widget n]]
          , forall n. Table n -> ColumnAlignment
defaultColumnAlignment :: ColumnAlignment
          , forall n. Table n -> RowAlignment
defaultRowAlignment :: RowAlignment
          , forall n. Table n -> Bool
drawSurroundingBorder :: Bool
          , forall n. Table n -> Bool
drawRowBorders :: Bool
          , forall n. Table n -> Bool
drawColumnBorders :: Bool
          }

-- | Construct a new table.
--
-- The argument is the list of rows with the topmost row first, with
-- each element of the argument list being the contents of the cells in
-- in each column of the respective row, with the leftmost cell first.
--
-- Each row's height is determined by the height of the tallest cell
-- in that row, and each column's width is determined by the width of
-- the widest cell in that column. This means that control over row
-- and column dimensions is a matter of controlling the size of the
-- individual cells, such as by wrapping cell contents in padding,
-- 'fill' and 'hLimit' or 'vLimit', etc. This also means that it is not
-- necessary to explicitly set the width of most table cells because
-- the table will determine the per-row and per-column dimensions by
-- looking at the largest cell contents. In particular, this means
-- that the table's alignment logic only has an effect when a given
-- cell's contents are smaller than the maximum for its row and column,
-- thus giving the table some way to pad the contents to result in the
-- desired alignment.
--
-- By default:
--
-- * All columns are left-aligned. Use the alignment functions in this
-- module to change that behavior.
-- * All rows are top-aligned. Use the alignment functions in this
-- module to change that behavior.
-- * The table will draw borders between columns, between rows, and
-- around the outside of the table. Border-drawing behavior can be
-- configured with the API in this module. Note that tables always draw
-- with 'joinBorders' enabled. If a cell's contents has smart borders
-- but you don't want those borders to connect to the surrounding table
-- borders, wrap the cell's contents with 'freezeBorders'.
--
-- All cells of all rows MUST use the 'Fixed' growth policy for both
-- horizontal and vertical growth. If the argument list contains any
-- cells that use the 'Greedy' policy, this function will raise a
-- 'TableException'.
--
-- All rows MUST have the same number of cells. If not, this function
-- will raise a 'TableException'.
table :: [[Widget n]] -> Table n
table :: forall n. [[Widget n]] -> Table n
table [[Widget n]]
rows =
    if | Bool -> Bool
not Bool
allFixed      -> forall a e. Exception e => e -> a
E.throw TableException
TEInvalidCellSizePolicy
       | Bool -> Bool
not Bool
allSameLength -> forall a e. Exception e => e -> a
E.throw TableException
TEUnequalRowSizes
       | Bool
otherwise         -> Table n
t
    where
        allSameLength :: Bool
allSameLength = forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall a. Eq a => [a] -> [a]
nub (forall (t :: * -> *) a. Foldable t => t a -> Int
length forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Widget n]]
rows)) forall a. Ord a => a -> a -> Bool
<= Int
1
        allFixed :: Bool
allFixed = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all forall {n}. [Widget n] -> Bool
fixedRow [[Widget n]]
rows
        fixedRow :: [Widget n] -> Bool
fixedRow = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all forall {n}. Widget n -> Bool
fixedCell
        fixedCell :: Widget n -> Bool
fixedCell Widget n
w = forall n. Widget n -> Size
hSize Widget n
w forall a. Eq a => a -> a -> Bool
== Size
Fixed Bool -> Bool -> Bool
&& forall n. Widget n -> Size
vSize Widget n
w forall a. Eq a => a -> a -> Bool
== Size
Fixed
        t :: Table n
t = Table { columnAlignments :: Map Int ColumnAlignment
columnAlignments = forall a. Monoid a => a
mempty
                  , rowAlignments :: Map Int RowAlignment
rowAlignments = forall a. Monoid a => a
mempty
                  , tableRows :: [[Widget n]]
tableRows = [[Widget n]]
rows
                  , drawSurroundingBorder :: Bool
drawSurroundingBorder = Bool
True
                  , drawRowBorders :: Bool
drawRowBorders = Bool
True
                  , drawColumnBorders :: Bool
drawColumnBorders = Bool
True
                  , defaultColumnAlignment :: ColumnAlignment
defaultColumnAlignment = ColumnAlignment
AlignLeft
                  , defaultRowAlignment :: RowAlignment
defaultRowAlignment = RowAlignment
AlignTop
                  }

-- | Configure whether the table draws a border on its exterior.
surroundingBorder :: Bool -> Table n -> Table n
surroundingBorder :: forall n. Bool -> Table n -> Table n
surroundingBorder Bool
b Table n
t =
    Table n
t { drawSurroundingBorder :: Bool
drawSurroundingBorder = Bool
b }

-- | Configure whether the table draws borders between its rows.
rowBorders :: Bool -> Table n -> Table n
rowBorders :: forall n. Bool -> Table n -> Table n
rowBorders Bool
b Table n
t =
    Table n
t { drawRowBorders :: Bool
drawRowBorders = Bool
b }

-- | Configure whether the table draws borders between its columns.
columnBorders :: Bool -> Table n -> Table n
columnBorders :: forall n. Bool -> Table n -> Table n
columnBorders Bool
b Table n
t =
    Table n
t { drawColumnBorders :: Bool
drawColumnBorders = Bool
b }

-- | Align the specified column to the right. The argument is the column
-- index, starting with zero. Silently does nothing if the index is out
-- of range.
alignRight :: Int -> Table n -> Table n
alignRight :: forall n. Int -> Table n -> Table n
alignRight = forall n. ColumnAlignment -> Int -> Table n -> Table n
setColAlignment ColumnAlignment
AlignRight

-- | Align the specified column to the left. The argument is the column
-- index, starting with zero. Silently does nothing if the index is out
-- of range.
alignLeft :: Int -> Table n -> Table n
alignLeft :: forall n. Int -> Table n -> Table n
alignLeft = forall n. ColumnAlignment -> Int -> Table n -> Table n
setColAlignment ColumnAlignment
AlignLeft

-- | Align the specified column to center. The argument is the column
-- index, starting with zero. Silently does nothing if the index is out
-- of range.
alignCenter :: Int -> Table n -> Table n
alignCenter :: forall n. Int -> Table n -> Table n
alignCenter = forall n. ColumnAlignment -> Int -> Table n -> Table n
setColAlignment ColumnAlignment
AlignCenter

-- | Align the specified row to the top. The argument is the row index,
-- starting with zero. Silently does nothing if the index is out of
-- range.
alignTop :: Int -> Table n -> Table n
alignTop :: forall n. Int -> Table n -> Table n
alignTop = forall n. RowAlignment -> Int -> Table n -> Table n
setRowAlignment RowAlignment
AlignTop

-- | Align the specified row to the middle. The argument is the row
-- index, starting with zero. Silently does nothing if the index is out
-- of range.
alignMiddle :: Int -> Table n -> Table n
alignMiddle :: forall n. Int -> Table n -> Table n
alignMiddle = forall n. RowAlignment -> Int -> Table n -> Table n
setRowAlignment RowAlignment
AlignMiddle

-- | Align the specified row to bottom. The argument is the row index,
-- starting with zero. Silently does nothing if the index is out of
-- range.
alignBottom :: Int -> Table n -> Table n
alignBottom :: forall n. Int -> Table n -> Table n
alignBottom = forall n. RowAlignment -> Int -> Table n -> Table n
setRowAlignment RowAlignment
AlignBottom

-- | Set the alignment for the specified column index (starting at
-- zero). Silently does nothing if the index is out of range.
setColAlignment :: ColumnAlignment -> Int -> Table n -> Table n
setColAlignment :: forall n. ColumnAlignment -> Int -> Table n -> Table n
setColAlignment ColumnAlignment
a Int
col Table n
t =
    Table n
t { columnAlignments :: Map Int ColumnAlignment
columnAlignments = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Int
col ColumnAlignment
a (forall n. Table n -> Map Int ColumnAlignment
columnAlignments Table n
t) }

-- | Set the alignment for the specified row index (starting at
-- zero). Silently does nothing if the index is out of range.
setRowAlignment :: RowAlignment -> Int -> Table n -> Table n
setRowAlignment :: forall n. RowAlignment -> Int -> Table n -> Table n
setRowAlignment RowAlignment
a Int
row Table n
t =
    Table n
t { rowAlignments :: Map Int RowAlignment
rowAlignments = forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Int
row RowAlignment
a (forall n. Table n -> Map Int RowAlignment
rowAlignments Table n
t) }

-- | Set the default column alignment for columns with no explicitly
-- configured alignment.
setDefaultColAlignment :: ColumnAlignment -> Table n -> Table n
setDefaultColAlignment :: forall n. ColumnAlignment -> Table n -> Table n
setDefaultColAlignment ColumnAlignment
a Table n
t =
    Table n
t { defaultColumnAlignment :: ColumnAlignment
defaultColumnAlignment = ColumnAlignment
a }

-- | Set the default row alignment for rows with no explicitly
-- configured alignment.
setDefaultRowAlignment :: RowAlignment -> Table n -> Table n
setDefaultRowAlignment :: forall n. RowAlignment -> Table n -> Table n
setDefaultRowAlignment RowAlignment
a Table n
t =
    Table n
t { defaultRowAlignment :: RowAlignment
defaultRowAlignment = RowAlignment
a }

-- | Render the table.
renderTable :: Table n -> Widget n
renderTable :: forall n. Table n -> Widget n
renderTable Table n
t =
    forall n. Widget n -> Widget n
joinBorders forall a b. (a -> b) -> a -> b
$
    forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Fixed Size
Fixed forall a b. (a -> b) -> a -> b
$ do
        Context n
ctx <- forall n. RenderM n (Context n)
getContext
        [[Result n]]
cellResults <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (forall n. Table n -> [[Widget n]]
tableRows Table n
t) forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall n. Widget n -> RenderM n (Result n)
render

        let maybeIntersperse :: (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse Table n -> Bool
f a
v = if Table n -> Bool
f Table n
t then forall a. a -> [a] -> [a]
intersperse a
v else forall a. a -> a
id
            rowHeights :: [Int]
rowHeights = forall {n}. [Result n] -> Int
rowHeight forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Result n]]
cellResults
            colWidths :: [Int]
colWidths = forall {n}. [Result n] -> Int
colWidth forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Result n]]
byColumn
            allRowAligns :: [RowAlignment]
allRowAligns = (\Int
i -> forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault (forall n. Table n -> RowAlignment
defaultRowAlignment Table n
t) Int
i (forall n. Table n -> Map Int RowAlignment
rowAlignments Table n
t)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                           [Int
0..forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
rowHeights forall a. Num a => a -> a -> a
- Int
1]
            allColAligns :: [ColumnAlignment]
allColAligns = (\Int
i -> forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault (forall n. Table n -> ColumnAlignment
defaultColumnAlignment Table n
t) Int
i (forall n. Table n -> Map Int ColumnAlignment
columnAlignments Table n
t)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                           [Int
0..forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Result n]]
byColumn forall a. Num a => a -> a -> a
- Int
1]
            rowHeight :: [Result n] -> Int
rowHeight = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Image -> Int
imageHeight forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Result n -> Image
image)
            colWidth :: [Result n] -> Int
colWidth = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Image -> Int
imageWidth forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall n. Result n -> Image
image)
            byColumn :: [[Result n]]
byColumn = forall a. [[a]] -> [[a]]
transpose [[Result n]]
cellResults
            toW :: Result n -> Widget n
toW = forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Fixed Size
Fixed forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Monad m => a -> m a
return
            fillEmptyCell :: d -> d -> Result n -> Result n
fillEmptyCell d
w d
h Result n
result =
                if Image -> Int
imageWidth (forall n. Result n -> Image
image Result n
result) forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Image -> Int
imageHeight (forall n. Result n -> Image
image Result n
result) forall a. Eq a => a -> a -> Bool
== Int
0
                then Result n
result { image :: Image
image = forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill (Context n
ctxforall s a. s -> Getting a s a -> a
^.forall r n. Getting r (Context n) Attr
attrL) Char
' ' d
w d
h }
                else Result n
result
            mkColumn :: (ColumnAlignment, Int, [Result n]) -> Widget n
mkColumn (ColumnAlignment
hAlign, Int
width, [Result n]
colCells) =
                let paddedCells :: [Widget n]
paddedCells = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [RowAlignment]
allRowAligns [Int]
rowHeights [Result n]
colCells) forall a b. (a -> b) -> a -> b
$ \(RowAlignment
vAlign, Int
rHeight, Result n
cell) ->
                        forall n. Int -> ColumnAlignment -> Widget n -> Widget n
applyColAlignment Int
width ColumnAlignment
hAlign forall a b. (a -> b) -> a -> b
$
                        forall n. Int -> RowAlignment -> Widget n -> Widget n
applyRowAlignment Int
rHeight RowAlignment
vAlign forall a b. (a -> b) -> a -> b
$
                        forall {n}. Result n -> Widget n
toW forall a b. (a -> b) -> a -> b
$
                        forall {d} {n}. Integral d => d -> d -> Result n -> Result n
fillEmptyCell Int
width Int
rHeight Result n
cell
                    maybeRowBorders :: [Widget n] -> [Widget n]
maybeRowBorders = forall {a}. (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse forall n. Table n -> Bool
drawRowBorders (forall n. Int -> Widget n -> Widget n
hLimit Int
width forall n. Widget n
hBorder)
                in forall n. [Widget n] -> Widget n
vBox forall a b. (a -> b) -> a -> b
$ forall {n}. [Widget n] -> [Widget n]
maybeRowBorders [Widget n]
paddedCells

            vBorders :: [Widget n]
vBorders = forall {n}. Int -> Widget n
mkVBorder forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int]
rowHeights
            hBorders :: [Widget n]
hBorders = forall {n}. Int -> Widget n
mkHBorder forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int]
colWidths
            mkHBorder :: Int -> Widget n
mkHBorder Int
w = forall n. Int -> Widget n -> Widget n
hLimit Int
w forall n. Widget n
hBorder
            mkVBorder :: Int -> Widget n
mkVBorder Int
h = forall n. Int -> Widget n -> Widget n
vLimit Int
h forall n. Widget n
vBorder
            topBorder :: Widget n
topBorder =
                forall n. [Widget n] -> Widget n
hBox forall a b. (a -> b) -> a -> b
$ forall {a}. (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse forall n. Table n -> Bool
drawColumnBorders forall n. Widget n
topT forall {n}. [Widget n]
hBorders
            bottomBorder :: Widget n
bottomBorder =
                forall n. [Widget n] -> Widget n
hBox forall a b. (a -> b) -> a -> b
$ forall {a}. (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse forall n. Table n -> Bool
drawColumnBorders forall n. Widget n
bottomT forall {n}. [Widget n]
hBorders
            leftBorder :: Widget n
leftBorder =
                forall n. [Widget n] -> Widget n
vBox forall a b. (a -> b) -> a -> b
$ forall n. Widget n
topLeftCorner forall a. a -> [a] -> [a]
: forall {a}. (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse forall n. Table n -> Bool
drawRowBorders forall n. Widget n
leftT forall {n}. [Widget n]
vBorders forall a. Semigroup a => a -> a -> a
<> [forall n. Widget n
bottomLeftCorner]
            rightBorder :: Widget n
rightBorder =
                forall n. [Widget n] -> Widget n
vBox forall a b. (a -> b) -> a -> b
$ forall n. Widget n
topRightCorner forall a. a -> [a] -> [a]
: forall {a}. (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse forall n. Table n -> Bool
drawRowBorders forall n. Widget n
rightT forall {n}. [Widget n]
vBorders forall a. Semigroup a => a -> a -> a
<> [forall n. Widget n
bottomRightCorner]

            maybeWrap :: (Table n -> Bool) -> (a -> a) -> a -> a
maybeWrap Table n -> Bool
check a -> a
f =
                if Table n -> Bool
check Table n
t then a -> a
f else forall a. a -> a
id
            addSurroundingBorder :: Widget n -> Widget n
addSurroundingBorder Widget n
body =
                forall n. Widget n
leftBorder forall n. Widget n -> Widget n -> Widget n
<+> (forall n. Widget n
topBorder forall n. Widget n -> Widget n -> Widget n
<=> Widget n
body forall n. Widget n -> Widget n -> Widget n
<=> forall n. Widget n
bottomBorder) forall n. Widget n -> Widget n -> Widget n
<+> forall n. Widget n
rightBorder
            addColumnBorders :: [Widget n] -> [Widget n]
addColumnBorders =
                let maybeAddCrosses :: [Widget n] -> [Widget n]
maybeAddCrosses = forall {a}. (Table n -> Bool) -> a -> [a] -> [a]
maybeIntersperse forall n. Table n -> Bool
drawRowBorders forall n. Widget n
cross
                    columnBorder :: Widget n
columnBorder = forall n. [Widget n] -> Widget n
vBox forall a b. (a -> b) -> a -> b
$ forall {n}. [Widget n] -> [Widget n]
maybeAddCrosses forall {n}. [Widget n]
vBorders
                in forall a. a -> [a] -> [a]
intersperse forall n. Widget n
columnBorder

        let columns :: [Widget n]
columns = forall {n}. (ColumnAlignment, Int, [Result n]) -> Widget n
mkColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [ColumnAlignment]
allColAligns [Int]
colWidths [[Result n]]
byColumn
            body :: Widget n
body = forall n. [Widget n] -> Widget n
hBox forall a b. (a -> b) -> a -> b
$
                   forall {a}. (Table n -> Bool) -> (a -> a) -> a -> a
maybeWrap forall n. Table n -> Bool
drawColumnBorders forall {n}. [Widget n] -> [Widget n]
addColumnBorders [Widget n]
columns
        forall n. Widget n -> RenderM n (Result n)
render forall a b. (a -> b) -> a -> b
$ forall {a}. (Table n -> Bool) -> (a -> a) -> a -> a
maybeWrap forall n. Table n -> Bool
drawSurroundingBorder forall n. Widget n -> Widget n
addSurroundingBorder Widget n
body

topLeftCorner :: Widget n
topLeftCorner :: forall n. Widget n
topLeftCorner = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
False Bool
True Bool
False Bool
True

topRightCorner :: Widget n
topRightCorner :: forall n. Widget n
topRightCorner = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
False Bool
True Bool
True Bool
False

bottomLeftCorner :: Widget n
bottomLeftCorner :: forall n. Widget n
bottomLeftCorner = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
True Bool
False Bool
False Bool
True

bottomRightCorner :: Widget n
bottomRightCorner :: forall n. Widget n
bottomRightCorner = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
True Bool
False Bool
True Bool
False

cross :: Widget n
cross :: forall n. Widget n
cross = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
True Bool
True Bool
True Bool
True

leftT :: Widget n
leftT :: forall n. Widget n
leftT = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
True Bool
True Bool
False Bool
True

rightT :: Widget n
rightT :: forall n. Widget n
rightT = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
True Bool
True Bool
True Bool
False

topT :: Widget n
topT :: forall n. Widget n
topT = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
False Bool
True Bool
True Bool
True

bottomT :: Widget n
bottomT :: forall n. Widget n
bottomT = forall n. Edges Bool -> Widget n
joinableBorder forall a b. (a -> b) -> a -> b
$ forall a. a -> a -> a -> a -> Edges a
Edges Bool
True Bool
False Bool
True Bool
True

applyColAlignment :: Int -> ColumnAlignment -> Widget n -> Widget n
applyColAlignment :: forall n. Int -> ColumnAlignment -> Widget n -> Widget n
applyColAlignment Int
width ColumnAlignment
align Widget n
w =
    forall n. Int -> Widget n -> Widget n
hLimit Int
width forall a b. (a -> b) -> a -> b
$ case ColumnAlignment
align of
        ColumnAlignment
AlignLeft   -> forall n. Padding -> Widget n -> Widget n
padRight Padding
Max Widget n
w
        ColumnAlignment
AlignCenter -> forall n. Widget n -> Widget n
hCenter Widget n
w
        ColumnAlignment
AlignRight  -> forall n. Padding -> Widget n -> Widget n
padLeft Padding
Max Widget n
w

applyRowAlignment :: Int -> RowAlignment -> Widget n -> Widget n
applyRowAlignment :: forall n. Int -> RowAlignment -> Widget n -> Widget n
applyRowAlignment Int
rHeight RowAlignment
align Widget n
w =
    forall n. Int -> Widget n -> Widget n
vLimit Int
rHeight forall a b. (a -> b) -> a -> b
$ case RowAlignment
align of
        RowAlignment
AlignTop    -> forall n. Padding -> Widget n -> Widget n
padBottom Padding
Max Widget n
w
        RowAlignment
AlignMiddle -> forall n. Widget n -> Widget n
vCenter Widget n
w
        RowAlignment
AlignBottom -> forall n. Padding -> Widget n -> Widget n
padTop Padding
Max Widget n
w