module Text.Taggy.Renderer where
import Data.Foldable (foldMap)
import Data.HashMap.Strict (HashMap, foldlWithKey')
import Data.Monoid ((<>))
import Data.Text (Text, unpack)
import Data.Text.Encoding (encodeUtf8)
import Text.Blaze (Markup)
import Text.Blaze.Renderer.Text (renderMarkup)
import Text.Taggy.DOM (Element(..), Node(..))
import qualified Data.Text.Lazy as Lazy (Text)
import Text.Blaze.Internal (ChoiceString(..), StaticString(..), MarkupM(..))
class AsMarkup a where
toMarkup :: Bool -> a -> Markup
instance AsMarkup Node where
toMarkup convertEntities = \case
#if MIN_VERSION_blaze_markup(0,8,0)
NodeContent text -> flip Content () $
#else
NodeContent text -> Content $
#endif
if convertEntities then Text text else PreEscaped (Text text)
NodeElement elmt -> toMarkup convertEntities elmt
instance AsMarkup Element where
toMarkup convertEntities Element{..} = eltAttrs `toAttribute` Parent tag begin end kids
where tag = toStatic eltName
begin = toStatic $ "<" <> eltName
end = toStatic $ "</" <> eltName <> ">"
kids = foldMap (toMarkup convertEntities) eltChildren
class Renderable a where
render :: a -> Lazy.Text
render = renderWith True
renderWith :: Bool -> a -> Lazy.Text
instance AsMarkup a => Renderable a where
renderWith = fmap renderMarkup . toMarkup
toAttribute :: HashMap Text Text -> (Markup -> Markup)
toAttribute = flip $ foldlWithKey' toAttribute'
where toAttribute' html attr value = AddCustomAttribute (Text attr) (Text value) html
toStatic :: Text -> StaticString
toStatic text = StaticString (unpack text ++) (encodeUtf8 text) text