{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
module Knit.Report.Input.Table.Colonnade
(
addColonnadeTextTable
, addColonnadeHtmlTable
, addColonnadeCellTable
, module Colonnade
, module Text.Blaze.Colonnade
)
where
import qualified Colonnade as C
import Colonnade
import qualified Text.Blaze.Colonnade as BC
import Text.Blaze.Colonnade
import qualified Text.Blaze.Html as BH
import qualified Text.Blaze.Html5.Attributes as BHA
import Knit.Report.Input.Html.Blaze ( addBlaze )
import Data.Text ( Text )
import qualified Polysemy as P
import qualified Knit.Effect.Pandoc as PE
import qualified Knit.Effect.PandocMonad as PM
addColonnadeTextTable
:: (PM.PandocEffects effs, P.Member PE.ToPandoc effs, Foldable f)
=> C.Colonnade C.Headed a Text
-> f a
-> P.Sem effs ()
addColonnadeTextTable :: Colonnade Headed a Text -> f a -> Sem effs ()
addColonnadeTextTable colonnade :: Colonnade Headed a Text
colonnade rows :: f a
rows = do
let toCell :: a -> Cell
toCell t :: a
t = Attribute -> Html -> Cell
BC.Cell (AttributeValue -> Attribute
BHA.style "border: 1px solid black") (a -> Html
forall a. ToMarkup a => a -> Html
BH.toHtml a
t)
Html -> Sem effs ()
forall (effs :: [(* -> *) -> * -> *]).
(PandocEffects effs, Member ToPandoc effs) =>
Html -> Sem effs ()
addBlaze (Html -> Sem effs ()) -> Html -> Sem effs ()
forall a b. (a -> b) -> a -> b
$ Attribute -> Colonnade Headed a Cell -> f a -> Html
forall (f :: * -> *) a.
Foldable f =>
Attribute -> Colonnade Headed a Cell -> f a -> Html
BC.encodeCellTable
(AttributeValue -> Attribute
BHA.style "border: 1px solid black; border-collapse: collapse")
((Text -> Cell)
-> Colonnade Headed a Text -> Colonnade Headed a Cell
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Cell
forall a. ToMarkup a => a -> Cell
toCell Colonnade Headed a Text
colonnade)
f a
rows
addColonnadeHtmlTable
:: (PM.PandocEffects effs, P.Member PE.ToPandoc effs, Foldable f)
=> BH.Attribute
-> C.Colonnade C.Headed a BH.Html
-> f a
-> P.Sem effs ()
addColonnadeHtmlTable :: Attribute -> Colonnade Headed a Html -> f a -> Sem effs ()
addColonnadeHtmlTable attr :: Attribute
attr colonnade :: Colonnade Headed a Html
colonnade rows :: f a
rows =
Html -> Sem effs ()
forall (effs :: [(* -> *) -> * -> *]).
(PandocEffects effs, Member ToPandoc effs) =>
Html -> Sem effs ()
addBlaze (Html -> Sem effs ()) -> Html -> Sem effs ()
forall a b. (a -> b) -> a -> b
$ Attribute -> Colonnade Headed a Html -> f a -> Html
forall (f :: * -> *) (h :: * -> *) a.
(Foldable f, Headedness h) =>
Attribute -> Colonnade h a Html -> f a -> Html
BC.encodeHtmlTable Attribute
attr Colonnade Headed a Html
colonnade f a
rows
addColonnadeCellTable
:: (PM.PandocEffects effs, P.Member PE.ToPandoc effs, Foldable f)
=> BH.Attribute
-> C.Colonnade C.Headed a BC.Cell
-> f a
-> P.Sem effs ()
addColonnadeCellTable :: Attribute -> Colonnade Headed a Cell -> f a -> Sem effs ()
addColonnadeCellTable attr :: Attribute
attr colonnade :: Colonnade Headed a Cell
colonnade rows :: f a
rows =
Html -> Sem effs ()
forall (effs :: [(* -> *) -> * -> *]).
(PandocEffects effs, Member ToPandoc effs) =>
Html -> Sem effs ()
addBlaze (Html -> Sem effs ()) -> Html -> Sem effs ()
forall a b. (a -> b) -> a -> b
$ Attribute -> Colonnade Headed a Cell -> f a -> Html
forall (f :: * -> *) a.
Foldable f =>
Attribute -> Colonnade Headed a Cell -> f a -> Html
BC.encodeCellTable Attribute
attr Colonnade Headed a Cell
colonnade f a
rows