{-# language OverloadedStrings #-}

-- | Produces XHTML 1.0 Strict.
module Text.XHtml.Strict (
     -- * Data types
     Html, HtmlAttr,
     -- * Classes
     HTML(..), ADDATTRS(..), CHANGEATTRS(..),
     -- * Primitives and basic combinators
     (<<), concatHtml, (+++),
     noHtml, isNoHtml, tag, itag,
     htmlAttrPair, emptyAttr, intAttr, strAttr, htmlAttr,
     primHtml, stringToHtmlString,
     docType,
     -- * Rendering
     showHtml, renderHtml, renderHtmlWithLanguage, prettyHtml,
     showHtmlFragment, renderHtmlFragment, prettyHtmlFragment,
     module Text.XHtml.Strict.Elements,
     module Text.XHtml.Strict.Attributes,
     module Text.XHtml.Extras
  ) where

import qualified Data.Text.Lazy as LText

import Text.XHtml.Internals
import Text.XHtml.Strict.Elements
import Text.XHtml.Strict.Attributes
import Text.XHtml.Extras

-- | The @DOCTYPE@ for XHTML 1.0 Strict.
docType :: Builder
docType :: Builder
docType = Builder
"<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\""
          forall a. Semigroup a => a -> a -> a
<> Builder
" \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">"

-- | Output the HTML without adding newlines or spaces within the markup.
--   This should be the most time and space efficient way to
--   render HTML, though the output is quite unreadable.
showHtml :: HTML html => html -> Builder
showHtml :: forall html. HTML html => html -> Builder
showHtml = forall html. HTML html => Builder -> html -> Builder
showHtmlInternal Builder
docType

{-# SPECIALIZE showHtml :: Html -> Builder #-}
{-# INLINABLE showHtml #-}

-- | Outputs indented HTML. Because space matters in
--   HTML, the output is quite messy.
renderHtml :: HTML html => html -> Builder
renderHtml :: forall html. HTML html => html -> Builder
renderHtml = forall html. HTML html => Builder -> html -> Builder
renderHtmlInternal Builder
docType

{-# SPECIALIZE renderHtml :: Html -> Builder #-}
{-# INLINABLE renderHtml #-}

-- | Outputs indented XHTML. Because space matters in
--   HTML, the output is quite messy.
renderHtmlWithLanguage :: HTML html
                       => LText.Text -- ^ The code of the "dominant" language of the webpage.
                       -> html -- ^ All the 'Html', including a header.
                       -> Builder
renderHtmlWithLanguage :: forall html. HTML html => Text -> html -> Builder
renderHtmlWithLanguage Text
l html
theHtml =
    Builder
docType forall a. Semigroup a => a -> a -> a
<> Builder
"\n" forall a. Semigroup a => a -> a -> a
<> forall html. HTML html => html -> Builder
renderHtmlFragment Html
code  forall a. Semigroup a => a -> a -> a
<> Builder
"\n"
  where
    code :: Html
code = Builder -> Html -> Html
tag Builder
"html" forall a. ADDATTRS a => a -> [HtmlAttr] -> a
! [ Builder -> Text -> HtmlAttr
strAttr Builder
"xmlns" Text
"http://www.w3.org/1999/xhtml"
                        , Builder -> Text -> HtmlAttr
strAttr Builder
"lang" Text
l
                        , Builder -> Text -> HtmlAttr
strAttr Builder
"xml:lang" Text
l
                        ] forall a b. HTML a => (Html -> b) -> a -> b
<< html
theHtml

-- | Outputs indented HTML, with indentation inside elements.
--   This can change the meaning of the HTML document, and
--   is mostly useful for debugging the HTML output.
--   The implementation is inefficient, and you are normally
--   better off using 'showHtml' or 'renderHtml'.
prettyHtml :: HTML html => html -> String
prettyHtml :: forall html. HTML html => html -> String
prettyHtml = forall html. HTML html => String -> html -> String
prettyHtmlInternal (Builder -> String
builderToString Builder
docType)