module Text.SimpleTableGenerator (
makeSimpleTable,
makeDefaultSimpleTable,
SimpleTableConfig (..),
simpleTableConfig,
simpleTableLeftPad,
simpleTableCenterPad,
simpleTableRightPad,
simpleTableBottomPad,
simpleTableMiddlePad,
simpleTableTopPad,
) where
import Data.List.Split (splitOn)
import Data.List (transpose)
type CellLine = String
type Cell = [CellLine]
type Row = [Cell]
type Table = [Row]
type CellSize = (Int, Int)
type CellSizeTable = [[CellSize]]
type TextTable = [[String]]
data CellWrapper =
CellWrapper {
cell :: Cell,
rowNum :: Int, colNum :: Int, cellWidth :: Int, cellHeight :: Int,
topLeft :: String, top :: String, topRight :: String, right :: String, bottomRight :: String,
bottom :: String, bottomLeft :: String, left :: String
} deriving (Show)
data SimpleTableConfig =
SimpleTableConfig {
tableBorders :: String,
colMinWidths :: [Int],
rowMinHeights :: [Int],
padFunction :: String -> Int -> String -> String,
cellPadFunction :: String -> Int -> [String] -> [String],
horizontalPadding :: Int,
verticalPadding :: Int,
paddingStr :: String,
emptyCellStr :: String
}
simpleTableConfig =
SimpleTableConfig {
tableBorders = "┌┬┐├┼┤└┴┘─│",
colMinWidths = [],
rowMinHeights = [],
padFunction = simpleTableRightPad,
cellPadFunction = simpleTableBottomPad,
horizontalPadding = 1,
verticalPadding = 0,
paddingStr = " ",
emptyCellStr = ""
}
makeDefaultSimpleTable table =
makeSimpleTable simpleTableConfig table
makeSimpleTable :: SimpleTableConfig -> [[String]] -> String
makeSimpleTable config table =
showTable $
map2d cell $
appendBorders $
normalizeBorderLengths $
wrapTable processedConfig $
padTableCells processedConfig $
makeCells $
normalizeColumnCount processedConfig $ table
where
processedConfig =
constructPaddingFunctions $ validateConfig config
normalizeColumnCount :: SimpleTableConfig -> TextTable -> TextTable
normalizeColumnCount config = normalizeColumnCountWithStr (emptyCellStr config)
normalizeColumnCountWithStr :: String -> TextTable -> TextTable
normalizeColumnCountWithStr emptyCellStr textTable =
map (\row -> addExtraCells row) textTable
where
addExtraCells row
| length row < columnCount = row ++ (take (columnCount length row)
$ repeat emptyCellStr)
| otherwise = row
columnCount = fst $ get2DListSize textTable
makeCells :: TextTable -> Table
makeCells textTable =
map (\rowStr -> map
(\cellStr -> splitOn "\n" cellStr) rowStr) textTable
where
splitCell :: String -> Cell
splitCell cellStr = splitOn "\n" cellStr
get2DListSize :: [[a]] -> (Int, Int)
get2DListSize list2d = (maximum $ map length list2d, length list2d)
padTableCells :: SimpleTableConfig -> Table -> Table
padTableCells config table = (padCellLines . addCellLines) table
where
addCellLines table = zipWith addExtraCellLines table realRowHeights
addExtraCellLines row height = map
(\cell -> (cellPadFunction config) "\n" height cell) row
padCellLines table = transpose $
zipWith padCellList (transpose table) realColWidths
padCellList col width = map (\cell -> map
(\celLine ->
(padFunction config)
(paddingStr config)
width celLine)
cell) col
realColWidths = zipWith max (colWidths cellSizeTable) ((colMinWidths config) ++ (repeat 0))
realRowHeights = zipWith max (rowHeights cellSizeTable) ((rowMinHeights config) ++ (repeat 0))
cellSizeTable = map2d get2DListSize table
rowHeights :: CellSizeTable -> [Int]
rowHeights sizeTable = maxOfMap2 snd sizeTable
colWidths :: CellSizeTable -> [Int]
colWidths sizeTable = maxOfMap2 fst $ transpose sizeTable
maxOfMap2 :: (a -> Int) -> [[a]] -> [Int]
maxOfMap2 f = map (\sth -> maximum $ map f sth)
wrapTable config table = wrapCells $ addCellCoords table
where
addCellCoords :: Table -> [[(Int, Int, Cell)]]
addCellCoords table = zipWith
(\ rowNum list ->
map (\ (colNum, cell) ->
(rowNum, colNum, cell)) list) [1..] $
map (zip [1..]) table
wrapCells :: [[(Int, Int, Cell)]] -> [[CellWrapper]]
wrapCells = map2d wrapCell
wrapCell :: (Int, Int, Cell) -> CellWrapper
wrapCell (rowNum, colNum, cell) =
(CellWrapper cell rowNum colNum
(maximum $ map length cell)
(length cell)
topLeft top topRight right bottomRight bottom bottomLeft left)
where
(width, height) = get2DListSize table
borders = tableBorders config
topLeft
| rowNum == 1 && colNum == 1 = [borders !! 0]
| colNum == 1 = [borders !! 3]
| rowNum == 1 = [borders !! 1]
| otherwise = [borders !! 4]
topRight
| rowNum == 1 && colNum == width = [borders !! 2]
| rowNum /= 1 && colNum == width = [borders !! 5]
| otherwise = ""
right
| colNum == width = [borders !! 10]
| otherwise = ""
bottomRight
| rowNum == height && colNum == width = [borders !! 8]
| rowNum == height = [borders !! 7]
| colNum == width = [borders !! 5]
| otherwise = ""
bottom
| rowNum == height = [borders !! 9]
| otherwise = ""
bottomLeft
| rowNum == height && colNum == 1 = [borders !! 6]
| rowNum == height = [borders !! 7]
| otherwise = ""
top = [borders !! 9]
left = [borders !! 10]
normalizeBorderLengths :: [[CellWrapper]] -> [[CellWrapper]]
normalizeBorderLengths =
map2d normalizeBorderLength
where
normalizeBorderLength :: CellWrapper -> CellWrapper
normalizeBorderLength
(CellWrapper cell rowNum colNum cellWidth cellHeight topLeft
top topRight right bottomRight bottom bottomLeft left) =
(CellWrapper cell rowNum colNum cellWidth cellHeight topLeft
(takeOf cellWidth top) topRight
right bottomRight
(takeOf cellWidth bottom) bottomLeft
left)
where
takeOf n sth =
take n $ concat $ repeat sth
appendBorders :: [[CellWrapper]] -> [[CellWrapper]]
appendBorders table =
map2d appendAll table
where
appendAll
(CellWrapper cell rowNum colNum cellWidth cellHeight topLeft
top topRight right bottomRight bottom bottomLeft left) =
(CellWrapper
((
(\ cell ->
if rowNum == height then
(init cell) ++ [bottomLeft ++ last cell]
else
cell) .
(\ cell ->
if colNum == width && rowNum == height then
(init cell) ++ [last cell ++ bottomRight]
else
cell) .
(\ cell ->
if rowNum == height then
cell ++ [bottom]
else
cell) .
(\ cell ->
if colNum == width then
[head cell] ++ (zipWith (++) (tail cell) (repeat right))
else
cell) .
(\ cell ->
(head cell ++ topRight):(tail cell)) .
(\ cell ->
[head cell] ++ zipWith (++) (repeat left) (tail cell)) .
(\ cell -> (concat (topLeft : [head cell])):(tail cell)) .
(\ cell -> top:cell))
cell)
rowNum colNum cellWidth cellHeight topLeft
top topRight right bottomRight bottom bottomLeft left)
width = fst $ get2DListSize table
height = snd $ get2DListSize table
showTable :: [[[String]]] -> String
showTable textTable = strJoin "\n" $
map (strJoin "\n") $
map2d (strJoin "") $
map transpose textTable
where
strJoin :: String -> [String] -> String
strJoin separator lst = if null lst then
""
else
foldr1 (\x y -> x ++ separator ++ y) lst
simpleTableLeftPad :: String -> Int -> String -> String
simpleTableLeftPad paddingStr width str
| length str > width = error "SimpleTableGenerator: String's length is greater than maximum!"
| otherwise = padding ++ str
where
padding = take (width length str) $ concat $ repeat paddingStr
simpleTableRightPad :: String -> Int -> String -> String
simpleTableRightPad paddingStr width str
| length str > width = error "SimpleTableGenerator: String's length is greater than maximum!"
| otherwise = str ++ padding
where
padding = take (width length str) $ concat $ repeat paddingStr
simpleTableCenterPad :: String -> Int -> String -> String
simpleTableCenterPad paddingStr width str
| length str > width = error "SimpleTableGenerator: String's length is greater than maximum!"
| even (width length str) = halfPadding ++ str ++ halfPadding
| otherwise = halfPadding ++ str ++ take (halfWidth + 1) padding
where
halfWidth = ((width length str) `div` 2)
padding = concat $ repeat paddingStr
halfPadding = take halfWidth padding
simpleTableBottomPad :: String -> Int -> Cell -> [String]
simpleTableBottomPad cellStr height cell
| length cell > height = error "SimpleTableGenerator: Cell's height is greater than maximum!"
| length cell == height = cell
| otherwise = cell ++ padding
where
padding = replicate (height length cell) ""
simpleTableTopPad :: String -> Int -> Cell -> [String]
simpleTableTopPad cellStr height cell
| length cell > height = error "SimpleTableGenerator: Cell's height is greater than maximum!"
| length cell == height = cell
| otherwise = padding ++ cell
where
padding = replicate (height length cell) ""
simpleTableMiddlePad :: String -> Int -> Cell -> [String]
simpleTableMiddlePad cellStr height cell
| length cell > height = error "SimpleTableGenerator: Cell's height is greater than maximum!"
| length cell == height = cell
| even (height length cell) = halfPadding ++ cell ++ halfPadding
| otherwise = halfPadding ++ cell ++ halfPadding ++ [""]
where
halfPadding = replicate ((height length cell) `div` 2) ""
constructPaddingFunctions :: SimpleTableConfig -> SimpleTableConfig
constructPaddingFunctions config = config {
padFunction = (\ f padStr width ->
let padding = take (horizontalPadding config) $
concat $ repeat (paddingStr config) in
padding ++ (f padStr width) ++ padding)
. (padFunction config),
cellPadFunction =
(\ f cellStr height ->
let padding = (concat
$ take (verticalPadding config)
$ repeat [""]) in
padding ++ (f cellStr height) ++ padding) .
(cellPadFunction config),
horizontalPadding = 0,
verticalPadding = 0
}
validateConfig config
| 0 == length (paddingStr config) = error "SimpleTableGenerator: paddingStr is empty!"
| 11 /= length (tableBorders config) = error "SimpleTableGenerator: tableBorders must be a string of 11 characters!"
| 0 > horizontalPadding config = error "SimpleTableGenerator: horizontalPadding must be >= 0!"
| 0 > verticalPadding config = error "SimpleTableGenerator: verticalPadding must be >= 0!"
| otherwise = config
map2d :: (a -> b) -> [[a]] -> [[b]]
map2d = map . map