-- | Support for basic table drawing.
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
import Graphics.Vty (imageHeight, imageWidth)

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

-- | Column alignment modes.
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
(ColumnAlignment -> ColumnAlignment -> Bool)
-> (ColumnAlignment -> ColumnAlignment -> Bool)
-> Eq ColumnAlignment
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
(Int -> ColumnAlignment -> ShowS)
-> (ColumnAlignment -> String)
-> ([ColumnAlignment] -> ShowS)
-> Show ColumnAlignment
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]
(Int -> ReadS ColumnAlignment)
-> ReadS [ColumnAlignment]
-> ReadPrec ColumnAlignment
-> ReadPrec [ColumnAlignment]
-> Read 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.
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
(RowAlignment -> RowAlignment -> Bool)
-> (RowAlignment -> RowAlignment -> Bool) -> Eq RowAlignment
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
(Int -> RowAlignment -> ShowS)
-> (RowAlignment -> String)
-> ([RowAlignment] -> ShowS)
-> Show RowAlignment
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]
(Int -> ReadS RowAlignment)
-> ReadS [RowAlignment]
-> ReadPrec RowAlignment
-> ReadPrec [RowAlignment]
-> Read 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
(TableException -> TableException -> Bool)
-> (TableException -> TableException -> Bool) -> Eq TableException
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
(Int -> TableException -> ShowS)
-> (TableException -> String)
-> ([TableException] -> ShowS)
-> Show TableException
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]
(Int -> ReadS TableException)
-> ReadS [TableException]
-> ReadPrec TableException
-> ReadPrec [TableException]
-> Read 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.
data Table n =
    Table { Table n -> Map Int ColumnAlignment
columnAlignments :: M.Map Int ColumnAlignment
          , Table n -> Map Int RowAlignment
rowAlignments :: M.Map Int RowAlignment
          , Table n -> [[Widget n]]
tableRows :: [[Widget n]]
          , Table n -> ColumnAlignment
defaultColumnAlignment :: ColumnAlignment
          , Table n -> RowAlignment
defaultRowAlignment :: RowAlignment
          , Table n -> Bool
drawSurroundingBorder :: Bool
          , Table n -> Bool
drawRowBorders :: Bool
          , Table n -> Bool
drawColumnBorders :: Bool
          }

-- | Construct a new table.
--
-- The argument is the list of rows, with each element of the argument
-- list being the columns of the respective row.
--
-- By default, all columns are left-aligned. Use the alignment functions
-- in this module to change that behavior.
--
-- By default, all rows are top-aligned. Use the alignment functions in
-- this module to change that behavior.
--
-- By default, 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.
--
-- 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 will raise a
-- 'TableException'.
--
-- All rows must have the same number of cells. If not, this will raise
-- a 'TableException'.
table :: [[Widget n]] -> Table n
table :: [[Widget n]] -> Table n
table [[Widget n]]
rows =
    if Bool -> Bool
not Bool
allFixed
    then TableException -> Table n
forall a e. Exception e => e -> a
E.throw TableException
TEInvalidCellSizePolicy
    else if Bool -> Bool
not Bool
allSameLength
         then TableException -> Table n
forall a e. Exception e => e -> a
E.throw TableException
TEUnequalRowSizes
         else Table n
t
    where
        allSameLength :: Bool
allSameLength = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Int] -> [Int]
forall a. Eq a => [a] -> [a]
nub ([Widget n] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Widget n] -> Int) -> [[Widget n]] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Widget n]]
rows)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
1
        allFixed :: Bool
allFixed = ([Widget n] -> Bool) -> [[Widget n]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [Widget n] -> Bool
forall n. [Widget n] -> Bool
fixedRow [[Widget n]]
rows
        fixedRow :: [Widget n] -> Bool
fixedRow = (Widget n -> Bool) -> [Widget n] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Widget n -> Bool
forall n. Widget n -> Bool
fixedCell
        fixedCell :: Widget n -> Bool
fixedCell Widget n
w = Widget n -> Size
forall n. Widget n -> Size
hSize Widget n
w Size -> Size -> Bool
forall a. Eq a => a -> a -> Bool
== Size
Fixed Bool -> Bool -> Bool
&& Widget n -> Size
forall n. Widget n -> Size
vSize Widget n
w Size -> Size -> Bool
forall a. Eq a => a -> a -> Bool
== Size
Fixed
        t :: Table n
t = Table :: forall n.
Map Int ColumnAlignment
-> Map Int RowAlignment
-> [[Widget n]]
-> ColumnAlignment
-> RowAlignment
-> Bool
-> Bool
-> Bool
-> Table n
Table { columnAlignments :: Map Int ColumnAlignment
columnAlignments = Map Int ColumnAlignment
forall a. Monoid a => a
mempty
                  , rowAlignments :: Map Int RowAlignment
rowAlignments = Map Int RowAlignment
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 :: 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 :: 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 :: 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.
alignRight :: Int -> Table n -> Table n
alignRight :: Int -> Table n -> Table n
alignRight = ColumnAlignment -> Int -> Table n -> Table n
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.
alignLeft :: Int -> Table n -> Table n
alignLeft :: Int -> Table n -> Table n
alignLeft = ColumnAlignment -> Int -> Table n -> Table n
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.
alignCenter :: Int -> Table n -> Table n
alignCenter :: Int -> Table n -> Table n
alignCenter = ColumnAlignment -> Int -> Table n -> Table n
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.
alignTop :: Int -> Table n -> Table n
alignTop :: Int -> Table n -> Table n
alignTop = RowAlignment -> Int -> Table n -> Table n
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.
alignMiddle :: Int -> Table n -> Table n
alignMiddle :: Int -> Table n -> Table n
alignMiddle = RowAlignment -> Int -> Table n -> Table n
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.
alignBottom :: Int -> Table n -> Table n
alignBottom :: Int -> Table n -> Table n
alignBottom = RowAlignment -> Int -> Table n -> Table n
forall n. RowAlignment -> Int -> Table n -> Table n
setRowAlignment RowAlignment
AlignBottom

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

-- | Set the alignment for the specified row index (starting at
-- zero).
setRowAlignment :: RowAlignment -> Int -> Table n -> Table n
setRowAlignment :: RowAlignment -> Int -> Table n -> Table n
setRowAlignment RowAlignment
a Int
row Table n
t =
    Table n
t { rowAlignments :: Map Int RowAlignment
rowAlignments = Int -> RowAlignment -> Map Int RowAlignment -> Map Int RowAlignment
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Int
row RowAlignment
a (Table n -> Map Int RowAlignment
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 :: 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 :: 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 :: Table n -> Widget n
renderTable Table n
t =
    Widget n -> Widget n
forall n. Widget n -> Widget n
joinBorders (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
    (if Table n -> Bool
forall n. Table n -> Bool
drawSurroundingBorder Table n
t then Widget n -> Widget n
forall n. Widget n -> Widget n
border else Widget n -> Widget n
forall a. a -> a
id) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
    Size -> Size -> RenderM n (Result n) -> Widget n
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Fixed Size
Fixed (RenderM n (Result n) -> Widget n)
-> RenderM n (Result n) -> Widget n
forall a b. (a -> b) -> a -> b
$ do
        let rows :: [[Widget n]]
rows = Table n -> [[Widget n]]
forall n. Table n -> [[Widget n]]
tableRows Table n
t
        [[Result n]]
cellResults <- [[Widget n]]
-> ([Widget n]
    -> ReaderT (Context n) (State (RenderState n)) [Result n])
-> ReaderT (Context n) (State (RenderState n)) [[Result n]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [[Widget n]]
rows (([Widget n]
  -> ReaderT (Context n) (State (RenderState n)) [Result n])
 -> ReaderT (Context n) (State (RenderState n)) [[Result n]])
-> ([Widget n]
    -> ReaderT (Context n) (State (RenderState n)) [Result n])
-> ReaderT (Context n) (State (RenderState n)) [[Result n]]
forall a b. (a -> b) -> a -> b
$ (Widget n -> RenderM n (Result n))
-> [Widget n]
-> ReaderT (Context n) (State (RenderState n)) [Result n]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render
        let rowHeights :: [Int]
rowHeights = [Result n] -> Int
forall n. [Result n] -> Int
rowHeight ([Result n] -> Int) -> [[Result n]] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Result n]]
cellResults
            colWidths :: [Int]
colWidths = [Result n] -> Int
forall n. [Result n] -> Int
colWidth ([Result n] -> Int) -> [[Result n]] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [[Result n]]
byColumn
            allRowAligns :: [RowAlignment]
allRowAligns = (\Int
i -> RowAlignment -> Int -> Map Int RowAlignment -> RowAlignment
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault (Table n -> RowAlignment
forall n. Table n -> RowAlignment
defaultRowAlignment Table n
t) Int
i (Table n -> Map Int RowAlignment
forall n. Table n -> Map Int RowAlignment
rowAlignments Table n
t)) (Int -> RowAlignment) -> [Int] -> [RowAlignment]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                           [Int
0..[Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
rowHeights Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
            allColAligns :: [ColumnAlignment]
allColAligns = (\Int
i -> ColumnAlignment
-> Int -> Map Int ColumnAlignment -> ColumnAlignment
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault (Table n -> ColumnAlignment
forall n. Table n -> ColumnAlignment
defaultColumnAlignment Table n
t) Int
i (Table n -> Map Int ColumnAlignment
forall n. Table n -> Map Int ColumnAlignment
columnAlignments Table n
t)) (Int -> ColumnAlignment) -> [Int] -> [ColumnAlignment]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                           [Int
0..[[Result n]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Result n]]
byColumn Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1]
            rowHeight :: [Result n] -> Int
rowHeight = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> ([Result n] -> [Int]) -> [Result n] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Result n -> Int) -> [Result n] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Image -> Int
imageHeight (Image -> Int) -> (Result n -> Image) -> Result n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result n -> Image
forall n. Result n -> Image
image)
            colWidth :: [Result n] -> Int
colWidth = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> ([Result n] -> [Int]) -> [Result n] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Result n -> Int) -> [Result n] -> [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Image -> Int
imageWidth (Image -> Int) -> (Result n -> Image) -> Result n -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result n -> Image
forall n. Result n -> Image
image)
            byColumn :: [[Result n]]
byColumn = [[Result n]] -> [[Result n]]
forall a. [[a]] -> [[a]]
transpose [[Result n]]
cellResults
            toW :: Result n -> Widget n
toW = Size -> Size -> RenderM n (Result n) -> Widget n
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Fixed Size
Fixed (RenderM n (Result n) -> Widget n)
-> (Result n -> RenderM n (Result n)) -> Result n -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Result n -> RenderM n (Result n)
forall (m :: * -> *) a. Monad m => a -> m a
return
            totalHeight :: Int
totalHeight = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Int]
rowHeights
            applyColAlignment :: ColumnAlignment -> Int -> Widget n -> Widget n
applyColAlignment ColumnAlignment
align Int
width Widget n
w =
                Size -> Size -> RenderM n (Result n) -> Widget n
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Fixed Size
Fixed (RenderM n (Result n) -> Widget n)
-> RenderM n (Result n) -> Widget n
forall a b. (a -> b) -> a -> b
$ do
                    Result n
result <- Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render Widget n
w
                    case ColumnAlignment
align of
                        ColumnAlignment
AlignLeft -> Result n -> RenderM n (Result n)
forall (m :: * -> *) a. Monad m => a -> m a
return Result n
result
                        ColumnAlignment
AlignCenter -> Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render (Widget n -> RenderM n (Result n))
-> Widget n -> RenderM n (Result n)
forall a b. (a -> b) -> a -> b
$ Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
hLimit Int
width (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Widget n -> Widget n
forall n. Widget n -> Widget n
hCenter (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Result n -> Widget n
forall n. Result n -> Widget n
toW Result n
result
                        ColumnAlignment
AlignRight -> Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render (Widget n -> RenderM n (Result n))
-> Widget n -> RenderM n (Result n)
forall a b. (a -> b) -> a -> b
$
                                          Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padLeft (Int -> Padding
Pad (Int
width Int -> Int -> Int
forall a. Num a => a -> a -> a
- Image -> Int
imageWidth (Result n -> Image
forall n. Result n -> Image
image Result n
result))) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
                                          Result n -> Widget n
forall n. Result n -> Widget n
toW Result n
result
            applyRowAlignment :: Int -> RowAlignment -> Result n -> Widget n
applyRowAlignment Int
rHeight RowAlignment
align Result n
result =
                case RowAlignment
align of
                 RowAlignment
AlignTop -> Result n -> Widget n
forall n. Result n -> Widget n
toW Result n
result
                 RowAlignment
AlignMiddle -> Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
vLimit Int
rHeight (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Widget n -> Widget n
forall n. Widget n -> Widget n
vCenter (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Result n -> Widget n
forall n. Result n -> Widget n
toW Result n
result
                 RowAlignment
AlignBottom -> Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
vLimit Int
rHeight (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Padding -> Widget n -> Widget n
forall n. Padding -> Widget n -> Widget n
padTop Padding
Max (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Result n -> Widget n
forall n. Result n -> Widget n
toW Result n
result
            mkColumn :: (ColumnAlignment, Int, [Result n]) -> RenderM n (Result n)
mkColumn (ColumnAlignment
hAlign, Int
width, [Result n]
colCells) = do
                let paddedCells :: [Widget n]
paddedCells = (((RowAlignment, Int, Result n) -> Widget n)
 -> [(RowAlignment, Int, Result n)] -> [Widget n])
-> [(RowAlignment, Int, Result n)]
-> ((RowAlignment, Int, Result n) -> Widget n)
-> [Widget n]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((RowAlignment, Int, Result n) -> Widget n)
-> [(RowAlignment, Int, Result n)] -> [Widget n]
forall a b. (a -> b) -> [a] -> [b]
map ([RowAlignment]
-> [Int] -> [Result n] -> [(RowAlignment, Int, Result n)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [RowAlignment]
allRowAligns [Int]
rowHeights [Result n]
colCells) (((RowAlignment, Int, Result n) -> Widget n) -> [Widget n])
-> ((RowAlignment, Int, Result n) -> Widget n) -> [Widget n]
forall a b. (a -> b) -> a -> b
$ \(RowAlignment
vAlign, Int
rHeight, Result n
cell) ->
                        ColumnAlignment -> Int -> Widget n -> Widget n
forall n. ColumnAlignment -> Int -> Widget n -> Widget n
applyColAlignment ColumnAlignment
hAlign Int
width (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
                        Int -> RowAlignment -> Result n -> Widget n
forall n. Int -> RowAlignment -> Result n -> Widget n
applyRowAlignment Int
rHeight RowAlignment
vAlign Result n
cell
                    maybeRowBorders :: [Widget n] -> [Widget n]
maybeRowBorders = if Table n -> Bool
forall n. Table n -> Bool
drawRowBorders Table n
t
                                      then Widget n -> [Widget n] -> [Widget n]
forall a. a -> [a] -> [a]
intersperse (Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
hLimit Int
width Widget n
forall n. Widget n
hBorder)
                                      else [Widget n] -> [Widget n]
forall a. a -> a
id
                Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render (Widget n -> RenderM n (Result n))
-> Widget n -> RenderM n (Result n)
forall a b. (a -> b) -> a -> b
$ [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
vBox ([Widget n] -> Widget n) -> [Widget n] -> Widget n
forall a b. (a -> b) -> a -> b
$ [Widget n] -> [Widget n]
forall n. [Widget n] -> [Widget n]
maybeRowBorders [Widget n]
paddedCells
        [Result n]
columns <- ((ColumnAlignment, Int, [Result n]) -> RenderM n (Result n))
-> [(ColumnAlignment, Int, [Result n])]
-> ReaderT (Context n) (State (RenderState n)) [Result n]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (ColumnAlignment, Int, [Result n]) -> RenderM n (Result n)
forall n.
(ColumnAlignment, Int, [Result n]) -> RenderM n (Result n)
mkColumn ([(ColumnAlignment, Int, [Result n])]
 -> ReaderT (Context n) (State (RenderState n)) [Result n])
-> [(ColumnAlignment, Int, [Result n])]
-> ReaderT (Context n) (State (RenderState n)) [Result n]
forall a b. (a -> b) -> a -> b
$ [ColumnAlignment]
-> [Int] -> [[Result n]] -> [(ColumnAlignment, Int, [Result n])]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [ColumnAlignment]
allColAligns [Int]
colWidths [[Result n]]
byColumn
        let maybeColumnBorders :: [Widget n] -> [Widget n]
maybeColumnBorders =
                if Table n -> Bool
forall n. Table n -> Bool
drawColumnBorders Table n
t
                then let rowBorderHeight :: Int
rowBorderHeight = if Table n -> Bool
forall n. Table n -> Bool
drawRowBorders Table n
t
                                           then [[Widget n]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Widget n]]
rows Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
                                           else Int
0
                     in Widget n -> [Widget n] -> [Widget n]
forall a. a -> [a] -> [a]
intersperse (Int -> Widget n -> Widget n
forall n. Int -> Widget n -> Widget n
vLimit (Int
totalHeight Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rowBorderHeight) Widget n
forall n. Widget n
vBorder)
                else [Widget n] -> [Widget n]
forall a. a -> a
id
        Widget n -> RenderM n (Result n)
forall n. Widget n -> RenderM n (Result n)
render (Widget n -> RenderM n (Result n))
-> Widget n -> RenderM n (Result n)
forall a b. (a -> b) -> a -> b
$ [Widget n] -> Widget n
forall n. [Widget n] -> Widget n
hBox ([Widget n] -> Widget n) -> [Widget n] -> Widget n
forall a b. (a -> b) -> a -> b
$ [Widget n] -> [Widget n]
forall n. [Widget n] -> [Widget n]
maybeColumnBorders ([Widget n] -> [Widget n]) -> [Widget n] -> [Widget n]
forall a b. (a -> b) -> a -> b
$ Result n -> Widget n
forall n. Result n -> Widget n
toW (Result n -> Widget n) -> [Result n] -> [Widget n]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Result n]
columns