lib: Write.Html.Attribute.tableStyle: style definitions taken from Commands.Balance.multiBalanceReportAsHtml

avoid duplicate with Write.Html.printHtml

Write.Html.Attribute: remove dependency on Lucid
This commit is contained in:
Henning Thielemann 2024-09-29 18:34:50 +02:00 committed by Simon Michael
parent a494e15d55
commit d8fc30f7c5
4 changed files with 26 additions and 25 deletions

View File

@ -23,12 +23,7 @@ import Data.Foldable (traverse_)
printHtml :: (Lines border) => [[Cell border (Lucid.Html ())]] -> Lucid.Html ()
printHtml table = do
Lucid.style_ $ Text.unlines $
"" :
"table {border-collapse:collapse}" :
"th, td {padding-left:1em}" :
"th.account, td.account {padding-left:0;}" :
[]
Lucid.style_ Attr.tableStylesheet
Lucid.table_ $ traverse_ formatRow table
formatRow:: (Lines border) => [Cell border (Lucid.Html ())] -> Lucid.Html ()
@ -50,7 +45,7 @@ formatCell cell =
let style =
case leftBorder++rightBorder++topBorder++bottomBorder of
[] -> []
ss -> [Attr.styles_ ss] in
ss -> [Lucid.style_ $ Attr.concatStyles ss] in
let class_ =
map Lucid.class_ $
filter (not . Text.null) [Spr.textFromClass $ cellClass cell] in

View File

@ -1,11 +1,12 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-} -- for stylesheet_
{- |
Helpers and CSS styles for HTML output.
-}
module Hledger.Write.Html.Attribute (
stylesheet_,
styles_,
stylesheet,
concatStyles,
tableStylesheet,
tableStyle,
bold,
doubleborder,
topdoubleborder,
@ -20,20 +21,27 @@ module Hledger.Write.Html.Attribute (
vpad,
) where
import qualified Lucid.Base as LucidBase
import qualified Lucid
import qualified Data.Text as Text
import Data.Text (Text)
-- | result can be 'Lucid.Attribute' or @Lucid.Html ()@
stylesheet_ :: LucidBase.TermRaw Text result => [(Text,Text)] -> result
stylesheet_ elstyles =
Lucid.style_ $ Text.unlines $
stylesheet :: [(Text,Text)] -> Text
stylesheet elstyles =
Text.unlines $
"" : [el<>" {"<>styles<>"}" | (el,styles) <- elstyles]
styles_ :: [Text] -> Lucid.Attribute
styles_ = Lucid.style_ . Text.intercalate "; "
concatStyles :: [Text] -> Text
concatStyles = Text.intercalate "; "
tableStylesheet :: Text
tableStylesheet = stylesheet tableStyle
tableStyle :: [(Text, Text)]
tableStyle =
[("table", collapse),
("th, td", lpad),
("th.account, td.account", "padding-left:0;")]
bold, doubleborder, topdoubleborder, bottomdoubleborder :: Text
bold = "font-weight:bold"

View File

@ -298,7 +298,7 @@ import Hledger.Cli.Utils
import Hledger.Write.Csv (CSV, printCSV, printTSV)
import Hledger.Write.Ods (printFods)
import Hledger.Write.Html (printHtml)
import Hledger.Write.Html.Attribute (stylesheet_, collapse, lpad)
import Hledger.Write.Html.Attribute (tableStylesheet)
import qualified Hledger.Write.Html as Html
import qualified Hledger.Write.Spreadsheet as Ods
@ -811,7 +811,7 @@ multiBalanceReportAsHtml ropts mbr =
let
(headingsrow,bodyrows,mtotalsrows) = multiBalanceReportHtmlRows ropts mbr
in do
stylesheet_ [("table",collapse), ("th, td",lpad), ("th.account, td.account","padding-left:0;")]
style_ tableStylesheet
table_ $ mconcat $
[headingsrow]
++ bodyrows

View File

@ -22,7 +22,7 @@ import qualified Data.Text.Lazy.Builder as TB
import Data.Time.Calendar (Day, addDays)
import System.Console.CmdArgs.Explicit as C (Mode, flagNone, flagReq)
import Hledger.Write.Csv (CSV, printCSV, printTSV)
import Hledger.Write.Html.Attribute (stylesheet_, collapse, lpad, alignleft, alignright)
import Hledger.Write.Html.Attribute (stylesheet, tableStyle, alignleft, alignright)
import qualified Hledger.Write.Html as Html
import qualified Hledger.Write.Spreadsheet as Spr
import Lucid as L hiding (value_)
@ -384,10 +384,8 @@ compoundBalanceReportAsHtml ropts cbr =
in do
link_ [rel_ "stylesheet", href_ "hledger.css"]
stylesheet_ [
("table",collapse),
("th, td",lpad),
("th.account, td.account","padding-left:0;"),
style_ $ stylesheet $
tableStyle ++ [
("td:nth-child(1)", "white-space:nowrap"),
("tr:nth-child(even) td", "background-color:#eee")
]