{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
module Lucid.Colonnade
(
encodeHtmlTable
, encodeCellTable
, encodeTable
, Cell(..)
, htmlCell
, stringCell
, textCell
, lazyTextCell
, builderCell
, htmlFromCell
) where
import Colonnade (Colonnade,Headed,Headless,Fascia,Cornice)
import Data.Text (Text)
import Control.Monad
import Data.Semigroup
import Data.Monoid hiding ((<>))
import Data.Foldable
import Data.String (IsString(..))
import Data.Maybe (listToMaybe)
import Data.Char (isSpace)
import Control.Applicative (liftA2)
import Lucid
import qualified Data.List as List
import qualified Colonnade.Encode as E
import qualified Data.Text as Text
import qualified Data.Text.Lazy as LText
import qualified Data.Text.Lazy.Builder as TBuilder
data Cell d = Cell
{ cellAttribute :: ![Attribute]
, cellHtml :: !(Html d)
}
instance (d ~ ()) => IsString (Cell d) where
fromString = stringCell
instance Semigroup d => Semigroup (Cell d) where
Cell a1 c1 <> Cell a2 c2 = Cell (mappend a1 a2) (liftA2 (<>) c1 c2)
instance Monoid d => Monoid (Cell d) where
mempty = Cell mempty (return mempty)
mappend (Cell a1 c1) (Cell a2 c2) = Cell (mappend a1 a2) (liftA2 mappend c1 c2)
htmlCell :: Html d -> Cell d
htmlCell = Cell mempty
stringCell :: String -> Cell ()
stringCell = htmlCell . fromString
charCell :: Char -> Cell ()
charCell = stringCell . pure
textCell :: Text -> Cell ()
textCell = htmlCell . toHtml
lazyTextCell :: LText.Text -> Cell ()
lazyTextCell = textCell . LText.toStrict
builderCell :: TBuilder.Builder -> Cell ()
builderCell = lazyTextCell . TBuilder.toLazyText
encodeHtmlTable ::
(E.Headedness h, Foldable f, Monoid d)
=> [Attribute]
-> Colonnade h a (Html d)
-> f a
-> Html d
encodeHtmlTable = encodeTable
(E.headednessPure ([],[])) mempty (const mempty) (\el -> el [])
encodeCellTable ::
(E.Headedness h, Foldable f, Monoid d)
=> [Attribute]
-> Colonnade h a (Cell d)
-> f a
-> Html d
encodeCellTable = encodeTable
(E.headednessPure ([],[])) mempty (const mempty) htmlFromCell
encodeTable :: forall f h a d c.
(Foldable f, E.Headedness h, Monoid d)
=> h ([Attribute],[Attribute])
-> [Attribute]
-> (a -> [Attribute])
-> (([Attribute] -> Html d -> Html d) -> c -> Html d)
-> [Attribute]
-> Colonnade h a c
-> f a
-> Html d
encodeTable mtheadAttrs tbodyAttrs trAttrs wrapContent tableAttrs colonnade xs =
table_ tableAttrs $ do
d1 <- case E.headednessExtractForall of
Nothing -> return mempty
Just extractForall -> do
let (theadAttrs,theadTrAttrs) = extract mtheadAttrs
thead_ theadAttrs $ tr_ theadTrAttrs $ do
foldlMapM' (wrapContent th_ . extract . E.oneColonnadeHead) (E.getColonnade colonnade)
where
extract :: forall y. h y -> y
extract = E.runExtractForall extractForall
d2 <- encodeBody trAttrs wrapContent tbodyAttrs colonnade xs
return (mappend d1 d2)
encodeBody :: (Foldable f, Monoid d)
=> (a -> [Attribute])
-> (([Attribute] -> Html d -> Html d) -> c -> Html d)
-> [Attribute]
-> Colonnade h a c
-> f a
-> Html d
encodeBody trAttrs wrapContent tbodyAttrs colonnade xs = do
tbody_ tbodyAttrs $ do
flip foldlMapM' xs $ \x -> do
tr_ (trAttrs x) $ E.rowMonadic colonnade (wrapContent td_) x
foldlMapM' :: forall g b a m. (Foldable g, Monoid b, Monad m) => (a -> m b) -> g a -> m b
foldlMapM' f xs = foldr f' pure xs mempty
where
f' :: a -> (b -> m b) -> b -> m b
f' x k bl = do
br <- f x
let !b = mappend bl br
k b
htmlFromCell :: ([Attribute] -> Html d -> Html d) -> Cell d -> Html d
htmlFromCell f (Cell attr content) = f attr content