implemented complexTable

This commit is contained in:
Jonathan Lamothe 2019-11-26 01:33:33 -05:00
parent d0f237e707
commit eedeaed8fc
2 changed files with 60 additions and 8 deletions

View File

@ -19,6 +19,8 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE LambdaCase #-}
module Mtlstats.Format
( padNum
, left
@ -29,10 +31,13 @@ module Mtlstats.Format
, labelTable
, numTable
, tableWith
, complexTable
) where
import Data.List (transpose)
import Mtlstats.Types
-- | Pad an 'Int' with leading zeroes to fit a certain character width
padNum
:: Int
@ -138,12 +143,32 @@ tableWith
-> [[String]]
-- ^ The cells
-> [String]
tableWith func tdata = let
widths = map (map length) tdata
tableWith pFunc tData = complexTable
(repeat pFunc)
(map (map CellText) tData)
-- | Creates a complex table
complexTable
:: [Int -> String -> String]
-- ^ The padding function for each column
-> [[TableCell]]
-- ^ The table cells (an array of rows)
-> [String]
complexTable pFuncs tData = let
widths = map
(map $ \case
CellText str -> length str
CellFill _ -> 0)
tData
colWidths = map maximum $ transpose widths
fitted = map
(\row -> map
(\(str, len) -> func len str) $
zip row colWidths)
tdata
in map unwords fitted
bFunc = \case
[] -> ""
[(f, len, CellText str)] -> f len str
[(_, len, CellFill ch)] -> replicate len ch
(f, len, CellText str) : cells -> f len str ++ " " ++ bFunc cells
(_, len, CellFill ch) : cells -> replicate (succ len) ch ++ bFunc cells
in map
(bFunc . zip3 pFuncs colWidths)
tData

View File

@ -24,6 +24,7 @@ module FormatSpec (spec) where
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Mtlstats.Format
import Mtlstats.Types
spec :: Spec
spec = describe "Mtlstats.Format" $ do
@ -36,6 +37,7 @@ spec = describe "Mtlstats.Format" $ do
labelTableSpec
numTableSpec
tableWithSpec
complexTableSpec
padNumSpec :: Spec
padNumSpec = describe "padNum" $ do
@ -174,3 +176,28 @@ tableWithSpec = describe "tableWith" $ let
]
)
]
complexTableSpec :: Spec
complexTableSpec = describe "complexTable" $ mapM_
(\(label, pFuncs, cells, expected) -> context label $
it "should format correctly" $
complexTable pFuncs cells `shouldBe` expected)
[ ( "no fill"
, [left, right]
, [ [ CellText "foo", CellText "bar" ]
, [ CellText "baaz", CellText "quux" ]
]
, [ "foo bar"
, "baaz quux"
]
)
, ( "with fill"
, [left, left, left]
, [ [ CellText "foo", CellText "bar", CellText "baz" ]
, [ CellText "quux", CellFill '-', CellFill '@' ]
]
, [ "foo bar baz"
, "quux ----@@@"
]
)
]