{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS -fno-warn-unused-do-bind #-} module Blaze.Html5 ( -- * Re-exports module Text.Blaze ,module Text.Blaze.Html5 ,module Text.Blaze.Html5.Attributes -- * Attribute combinators ,Attributable ,(!.) ,(!#) -- * Common operations ,linesToHtml ,htmlIntercalate ,htmlCommasAnd ,htmlCommas) where import Data.Monoid import Text.Blaze import Text.Blaze.Html5 hiding (map,style,title) import qualified Text.Blaze.Html5.Attributes as A import Text.Blaze.Html5.Attributes hiding (span,label,cite,form,summary,min) import Text.Blaze.Internal (Attributable) -- | Class attribute. (!.) :: (Attributable h) => h -> AttributeValue -> h e !. className = e ! A.class_ className -- | Id attribute. (!#) :: (Attributable h) => h -> AttributeValue -> h e !# idName = e ! A.id idName -- | Render the lines as HTML lines. linesToHtml :: [Html] -> Html linesToHtml = htmlIntercalate br -- | Intercalate the given things. htmlIntercalate :: Html -> [Html] -> Html htmlIntercalate _ [x] = x htmlIntercalate sep (x:xs) = do x; sep; htmlIntercalate sep xs htmlIntercalate _ [] = mempty -- | Show some HTML comma-separated with “and” inbetween to be grammatical. htmlCommasAnd :: [Html] -> Html htmlCommasAnd [x] = x htmlCommasAnd [x,y] = do x; " and "; y htmlCommasAnd (x:xs) = do x; ", "; htmlCommasAnd xs htmlCommasAnd [] = mempty -- | Comma-separate some HTML. htmlCommas :: [Html] -> Html htmlCommas = htmlIntercalate ", "