-- | (x)html related constants.
module Text.HTML.Light.Constant where

import Text.HTML.Light.Element
import Text.XML.Light

-- * Named non-ascii characters

c_entity :: String -> Content
c_entity s = cdata_raw ('&' : s ++ ";")

-- | The copyright character.
copy :: Content
copy = c_entity "copy"

-- | The down arrow character.
darr :: Content
darr = c_entity "darr"

-- | The double down arrow character.
dArr :: Content
dArr = c_entity "dArr"

-- | The degree character.
deg :: Content
deg = c_entity "deg"

-- | The horizontal ellipsis character.
hellip :: Content
hellip = c_entity "hellip"

-- | The left double arrow character.
larr :: Content
larr = c_entity "larr"

-- | The empty set symbol.
empty :: Content
empty = c_entity "empty"

-- | The left arrow character.
lArr :: Content
lArr = c_entity "lArr"

-- | The right double angle quote character.
laquo :: Content
laquo = c_entity "laquo"

-- | The mid (centre) dot character.
middot :: Content
middot = c_entity "middot"

-- | The non-breaking space character.
nbsp :: Content
nbsp = c_entity "nbsp"

-- | The right arrow character.
rarr :: Content
rarr = c_entity "rarr"

-- | The right double arrow character.
rArr :: Content
rArr = c_entity "rArr"

-- | The right double angle quote character.
raquo :: Content
raquo = c_entity "raquo"

-- | The dot operator.
sdot :: Content
sdot = c_entity "sdot"

-- | The up arrow character.
uarr :: Content
uarr = c_entity "uarr"

-- | The up double arrow character.
uArr :: Content
uArr = c_entity "uArr"

-- * Version and document type strings

-- | The xml version 1.0 string with UTF-8 encoding set.
xml_1_0 :: String
xml_1_0 = "<?xml version=\"1.0\" encoding=\"UTF-8\"?>"

-- | A type synonym for document type strings.
type DocType = String

-- | The xhtml 1.0 strict document type string.
xhtml_1_0_strict :: DocType
xhtml_1_0_strict =
    let dtd = "PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\""
        url = "\"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\""
    in concat ["<!DOCTYPE html ", dtd, " ", url, ">"]

-- | The xhtml 1.0 transitional document type string.
xhtml_1_0_transitional :: DocType
xhtml_1_0_transitional =
    let dtd = "PUBLIC \"-//W3C//DTD XHTML 1.0 Transitional//EN\""
        url = "\"http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd\""
    in concat ["<!DOCTYPE html ", dtd, " ", url, ">"]

-- | The HTML5 document type string.
html5_dt :: DocType
html5_dt = "<!DOCTYPE html>"