{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module TextShow.Text.XHtml () where
import Prelude ()
import Prelude.Compat
import Text.XHtml.Frameset (Html, HtmlAttr, HotLink,
htmlAttrPair, renderHtmlFragment)
import Text.XHtml.Table (HtmlTable)
import TextShow (TextShow(..), FromStringShow(..), fromString, singleton)
import TextShow.TH (deriveTextShow)
instance TextShow Html where
showb :: Html -> Builder
showb = String -> Builder
fromString (String -> Builder) -> (Html -> String) -> Html -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Html -> String
forall html. HTML html => html -> String
renderHtmlFragment
{-# INLINE showb #-}
showbList :: [Html] -> Builder
showbList = [Builder] -> Builder
forall a. Monoid a => [a] -> a
mconcat ([Builder] -> Builder)
-> ([Html] -> [Builder]) -> [Html] -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Html -> Builder) -> [Html] -> [Builder]
forall a b. (a -> b) -> [a] -> [b]
map Html -> Builder
forall a. TextShow a => a -> Builder
showb
{-# INLINE showbList #-}
instance TextShow HtmlAttr where
showb :: HtmlAttr -> Builder
showb HtmlAttr
ha = case HtmlAttr -> (String, String)
htmlAttrPair HtmlAttr
ha of
(String
str, String
val) -> String -> Builder
fromString String
str Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
'=' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> String -> Builder
forall a. TextShow a => a -> Builder
showb String
val
{-# INLINE showb #-}
$(deriveTextShow ''HotLink)
instance TextShow HtmlTable where
showb :: HtmlTable -> Builder
showb = FromStringShow HtmlTable -> Builder
forall a. TextShow a => a -> Builder
showb (FromStringShow HtmlTable -> Builder)
-> (HtmlTable -> FromStringShow HtmlTable) -> HtmlTable -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HtmlTable -> FromStringShow HtmlTable
forall a. a -> FromStringShow a
FromStringShow
{-# INLINE showb #-}