{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} -- | Module : Html -- Copyright : (c) Joshua Obritsch, 2021 -- License : MIT -- Maintainer : joshua@obritsch.com -- Stability : Experimental -- -- The "Html" module provides a set of types, classes and functions for generating HTML elements. -- -- These elements along with their attributes and event handlers, found in the "Html.Attributes" and "Html.Events" modules respectively, can -- be used to dynamically compose HTML documents natively in Haskell, without relying on templating engines or other techniques that can be -- error-prone and difficult to maintain. -- -- Additionally, the functions provided in the "Html.Intl" module can be used to facilitate internationalization. module Html ( -- * Types -- ** Html Html(..) -- ** Attribute , Attribute(..) -- * Classes -- ** Buildable , Buildable(..) -- ** Translatable , Translatable(..) -- * Declarations -- ** \ , doctype -- * Elements -- ** \ , a -- ** \ , abbr -- ** \ , address -- ** \ , area -- ** \ , article -- ** \ , aside -- ** \ , audio -- ** \ , b -- ** \ , base -- ** \ , bdi -- ** \ , bdo -- ** \ , blockquote -- ** \ , body -- ** \ , br -- ** \ , button -- ** \ , canvas -- ** \ , caption -- ** \ , cite -- ** \ , code -- ** \ , col -- ** \ , colgroup -- ** \ , data_ -- ** \ , datalist -- ** \ , dd -- ** \ , del -- ** \ , details -- ** \ , dfn -- ** \ , dialog -- ** \ , div -- ** \ , dl -- ** \ , dt -- ** \ , em -- ** \ , embed -- ** \ , fieldset -- ** \ , figcaption -- ** \ , figure -- ** \ , footer -- ** \ , form -- ** \ , h1 -- ** \ , h2 -- ** \ , h3 -- ** \ , h4 -- ** \ , h5 -- ** \ , h6 -- ** \ , head -- ** \ , header -- ** \ , hgroup -- ** \ , hr -- ** \ , html -- ** \ , i -- ** \ , iframe -- ** \ , img -- ** \ , input -- ** \ , ins -- ** \ , kbd -- ** \ , label -- ** \ , legend -- ** \ , li -- ** \ , link -- ** \ , main -- ** \ , map -- ** \ , mark -- ** \ , menu -- ** \ , meta -- ** \ , meter -- ** \ , nav -- ** \ , noscript -- ** \ , object -- ** \ , ol -- ** \ , optgroup -- ** \ , option -- ** \ , output -- ** \ , p -- ** \ , picture -- ** \ , pre -- ** \ , progress -- ** \ , q -- ** \ , rp -- ** \ , rt -- ** \ , ruby -- ** \ , s -- ** \ , samp -- ** \ , script -- ** \ , section -- ** \ , select -- ** \ , slot -- ** \ , small -- ** \ , source -- ** \ , span -- ** \ , strong -- ** \ , style -- ** \ , sub -- ** \ , summary -- ** \ , sup -- ** \ , table -- ** \ , tbody -- ** \ , td -- ** \ , template -- ** \ , textarea -- ** \ , tfoot -- ** \ , th -- ** \ , thead -- ** \ , time -- ** \ , title -- ** \ , tr -- ** \ , track -- ** \ , u -- ** \ , ul -- ** \ , var -- ** \ , video -- ** \ , wbr ) where import Data.Bool (Bool(..)) import Data.Foldable (foldr) import Data.Function ((.)) import Data.Monoid ((<>), mempty) import Data.String (IsString(..)) import Data.Text.Lazy (unpack) import Data.Text.Lazy.Builder (Builder, singleton, toLazyText) import Text.Show (Show(..)) -- TYPES -- | Represents an HTML element. -- -- /Note: The type variable /lng/ stands for /language/ and is used to facilitate internationalization./ data Html lng where -- | Constructs an HTML parent node. ParentNode :: Builder -> Builder -> [Attribute] -> [Html lng] -> Html lng -- | Constructs an HTML leaf node. LeafNode :: Builder -> [Attribute] -> Html lng -- | Constructs an HTML root node. RootNode :: Builder -> [Html lng] -> Html lng -- | Constructs a monolingual HTML text node. TextNode :: Builder -> Html lng -- | Constructs a multilingual HTML text node. IntlNode :: Translatable lng => lng -> Html lng instance IsString (Html lng) where fromString = TextNode . fromString instance Show (Html lng) where show = unpack . toLazyText . build instance Buildable (Html lng) where build html = case html of ParentNode startTag endTag [] [] -> startTag <> singleton '>' <> endTag ParentNode startTag endTag attributes [] -> startTag <> build attributes <> singleton '>' <> endTag ParentNode startTag endTag [] children -> startTag <> singleton '>' <> build children <> endTag ParentNode startTag endTag attributes children -> startTag <> build attributes <> singleton '>' <> build children <> endTag LeafNode startTag [] -> startTag <> singleton '>' LeafNode startTag attributes -> startTag <> build attributes <> singleton '>' RootNode startTag [] -> startTag RootNode startTag children -> startTag <> build children TextNode text -> text IntlNode intl -> text where text = defaultLanguage intl instance {-# OVERLAPPING #-} Show [Html lng] where show = unpack . toLazyText . build instance Buildable [Html lng] where build = foldr ((<>) . build) mempty -- | Represents an HTML attribute. data Attribute -- | Constructs a boolean HTML attribute. = BoolAttribute Builder Bool -- | Constructs a textual HTML attribute. | TextAttribute Builder Builder instance Show Attribute where show = unpack . toLazyText . build instance Buildable Attribute where build attribute = case attribute of BoolAttribute _ False -> mempty BoolAttribute key True -> key TextAttribute _ "" -> mempty TextAttribute key value -> key <> value <> singleton '"' instance {-# OVERLAPPING #-} Show [Attribute] where show = unpack . toLazyText . build instance Buildable [Attribute] where build = foldr ((<>) . build) mempty -- CLASSES -- | Enables conversion to 'Data.Text.Lazy.Builder.Builder'. class Buildable a where -- | Converts to 'Data.Text.Lazy.Builder.Builder'. build :: a -> Builder -- | Enables the use of multilingual text nodes with 'Html.Html'. class Translatable a where -- | Sets the default language to use for internationalization with 'Html.Html'. defaultLanguage :: a -> Builder -- DECLARATIONS -- | Generates an HTML @\@ declaration with the given contents. doctype :: [Html lng] -> Html lng doctype = RootNode "\n" {-# INLINE doctype #-} -- ELEMENTS -- | Generates an HTML @\@ element with the given attributes and contents. a :: [Attribute] -> [Html lng] -> Html lng a = ParentNode "" {-# INLINE a #-} -- | Generates an HTML @\@ element with the given attributes and contents. abbr :: [Attribute] -> [Html lng] -> Html lng abbr = ParentNode "" {-# INLINE abbr #-} -- | Generates an HTML @\@ element with the given attributes and contents. address :: [Attribute] -> [Html lng] -> Html lng address = ParentNode "" {-# INLINE address #-} -- | Generates an HTML @\@ element with the given attributes. area :: [Attribute] -> Html lng area = LeafNode "@ element with the given attributes and contents. article :: [Attribute] -> [Html lng] -> Html lng article = ParentNode "" {-# INLINE article #-} -- | Generates an HTML @\@ element with the given attributes and contents. aside :: [Attribute] -> [Html lng] -> Html lng aside = ParentNode "" {-# INLINE aside #-} -- | Generates an HTML @\@ element with the given attributes and contents. audio :: [Attribute] -> [Html lng] -> Html lng audio = ParentNode "" {-# INLINE audio #-} -- | Generates an HTML @\@ element with the given attributes and contents. b :: [Attribute] -> [Html lng] -> Html lng b = ParentNode "" {-# INLINE b #-} -- | Generates an HTML @\@ element with the given attributes. base :: [Attribute] -> Html lng base = LeafNode "@ element with the given attributes and contents. bdi :: [Attribute] -> [Html lng] -> Html lng bdi = ParentNode "" {-# INLINE bdi #-} -- | Generates an HTML @\@ element with the given attributes and contents. bdo :: [Attribute] -> [Html lng] -> Html lng bdo = ParentNode "" {-# INLINE bdo #-} -- | Generates an HTML @\@ element with the given attributes and contents. blockquote :: [Attribute] -> [Html lng] -> Html lng blockquote = ParentNode "" {-# INLINE blockquote #-} -- | Generates an HTML @\@ element with the given attributes and contents. body :: [Attribute] -> [Html lng] -> Html lng body = ParentNode "" {-# INLINE body #-} -- | Generates an HTML @\@ element with the given attributes. br :: [Attribute] -> Html lng br = LeafNode "@ element with the given attributes and contents. button :: [Attribute] -> [Html lng] -> Html lng button = ParentNode "" {-# INLINE button #-} -- | Generates an HTML @\@ element with the given attributes and contents. canvas :: [Attribute] -> [Html lng] -> Html lng canvas = ParentNode "" {-# INLINE canvas #-} -- | Generates an HTML @\@ element with the given attributes and contents. caption :: [Attribute] -> [Html lng] -> Html lng caption = ParentNode "" {-# INLINE caption #-} -- | Generates an HTML @\@ element with the given attributes and contents. cite :: [Attribute] -> [Html lng] -> Html lng cite = ParentNode "" {-# INLINE cite #-} -- | Generates an HTML @\@ element with the given attributes and contents. code :: [Attribute] -> [Html lng] -> Html lng code = ParentNode "" {-# INLINE code #-} -- | Generates an HTML @\@ element with the given attributes. col :: [Attribute] -> Html lng col = LeafNode "@ element with the given attributes and contents. colgroup :: [Attribute] -> [Html lng] -> Html lng colgroup = ParentNode "" {-# INLINE colgroup #-} -- | Generates an HTML @\@ element with the given attributes and contents. data_ :: [Attribute] -> [Html lng] -> Html lng data_ = ParentNode "" {-# INLINE data_ #-} -- | Generates an HTML @\@ element with the given attributes and contents. datalist :: [Attribute] -> [Html lng] -> Html lng datalist = ParentNode "" {-# INLINE datalist #-} -- | Generates an HTML @\@ element with the given attributes and contents. dd :: [Attribute] -> [Html lng] -> Html lng dd = ParentNode "" {-# INLINE dd #-} -- | Generates an HTML @\@ element with the given attributes and contents. del :: [Attribute] -> [Html lng] -> Html lng del = ParentNode "" {-# INLINE del #-} -- | Generates an HTML @\@ element with the given attributes and contents. details :: [Attribute] -> [Html lng] -> Html lng details = ParentNode "" {-# INLINE details #-} -- | Generates an HTML @\@ element with the given attributes and contents. dfn :: [Attribute] -> [Html lng] -> Html lng dfn = ParentNode "" {-# INLINE dfn #-} -- | Generates an HTML @\@ element with the given attributes and contents. dialog :: [Attribute] -> [Html lng] -> Html lng dialog = ParentNode "" {-# INLINE dialog #-} -- | Generates an HTML @\@ element with the given attributes and contents. div :: [Attribute] -> [Html lng] -> Html lng div = ParentNode "" {-# INLINE div #-} -- | Generates an HTML @\@ element with the given attributes and contents. dl :: [Attribute] -> [Html lng] -> Html lng dl = ParentNode "" {-# INLINE dl #-} -- | Generates an HTML @\@ element with the given attributes and contents. dt :: [Attribute] -> [Html lng] -> Html lng dt = ParentNode "" {-# INLINE dt #-} -- | Generates an HTML @\@ element with the given attributes and contents. em :: [Attribute] -> [Html lng] -> Html lng em = ParentNode "" {-# INLINE em #-} -- | Generates an HTML @\@ element with the given attributes. embed :: [Attribute] -> Html lng embed = LeafNode "@ element with the given attributes and contents. fieldset :: [Attribute] -> [Html lng] -> Html lng fieldset = ParentNode "" {-# INLINE fieldset #-} -- | Generates an HTML @\@ element with the given attributes and contents. figcaption :: [Attribute] -> [Html lng] -> Html lng figcaption = ParentNode "" {-# INLINE figcaption #-} -- | Generates an HTML @\@ element with the given attributes and contents. figure :: [Attribute] -> [Html lng] -> Html lng figure = ParentNode "" {-# INLINE figure #-} -- | Generates an HTML @\@ element with the given attributes and contents. footer :: [Attribute] -> [Html lng] -> Html lng footer = ParentNode "" {-# INLINE footer #-} -- | Generates an HTML @\@ element with the given attributes and contents. form :: [Attribute] -> [Html lng] -> Html lng form = ParentNode "" {-# INLINE form #-} -- | Generates an HTML @\@ element with the given attributes and contents. h1 :: [Attribute] -> [Html lng] -> Html lng h1 = ParentNode "" {-# INLINE h1 #-} -- | Generates an HTML @\@ element with the given attributes and contents. h2 :: [Attribute] -> [Html lng] -> Html lng h2 = ParentNode "" {-# INLINE h2 #-} -- | Generates an HTML @\@ element with the given attributes and contents. h3 :: [Attribute] -> [Html lng] -> Html lng h3 = ParentNode "" {-# INLINE h3 #-} -- | Generates an HTML @\@ element with the given attributes and contents. h4 :: [Attribute] -> [Html lng] -> Html lng h4 = ParentNode "" {-# INLINE h4 #-} -- | Generates an HTML @\@ element with the given attributes and contents. h5 :: [Attribute] -> [Html lng] -> Html lng h5 = ParentNode "" {-# INLINE h5 #-} -- | Generates an HTML @\@ element with the given attributes and contents. h6 :: [Attribute] -> [Html lng] -> Html lng h6 = ParentNode "" {-# INLINE h6 #-} -- | Generates an HTML @\@ element with the given attributes and contents. head :: [Attribute] -> [Html lng] -> Html lng head = ParentNode "" {-# INLINE head #-} -- | Generates an HTML @\@ element with the given attributes and contents. header :: [Attribute] -> [Html lng] -> Html lng header = ParentNode "" {-# INLINE header #-} -- | Generates an HTML @\@ element with the given attributes and contents. hgroup :: [Attribute] -> [Html lng] -> Html lng hgroup = ParentNode "" {-# INLINE hgroup #-} -- | Generates an HTML @\@ element with the given attributes. hr :: [Attribute] -> Html lng hr = LeafNode "@ element with the given attributes and contents. html :: [Attribute] -> [Html lng] -> Html lng html = ParentNode "" {-# INLINE html #-} -- | Generates an HTML @\@ element with the given attributes and contents. i :: [Attribute] -> [Html lng] -> Html lng i = ParentNode "" {-# INLINE i #-} -- | Generates an HTML @\@ element with the given attributes and contents. iframe :: [Attribute] -> [Html lng] -> Html lng iframe = ParentNode "" {-# INLINE iframe #-} -- | Generates an HTML @\@ element with the given attributes. img :: [Attribute] -> Html lng img = LeafNode "@ element with the given attributes. input :: [Attribute] -> Html lng input = LeafNode "@ element with the given attributes and contents. ins :: [Attribute] -> [Html lng] -> Html lng ins = ParentNode "" {-# INLINE ins #-} -- | Generates an HTML @\@ element with the given attributes and contents. kbd :: [Attribute] -> [Html lng] -> Html lng kbd = ParentNode "" {-# INLINE kbd #-} -- | Generates an HTML @\@ element with the given attributes and contents. label :: [Attribute] -> [Html lng] -> Html lng label = ParentNode "" {-# INLINE label #-} -- | Generates an HTML @\@ element with the given attributes and contents. legend :: [Attribute] -> [Html lng] -> Html lng legend = ParentNode "" {-# INLINE legend #-} -- | Generates an HTML @\@ element with the given attributes and contents. li :: [Attribute] -> [Html lng] -> Html lng li = ParentNode "" {-# INLINE li #-} -- | Generates an HTML @\@ element with the given attributes. link :: [Attribute] -> Html lng link = LeafNode "@ element with the given attributes and contents. main :: [Attribute] -> [Html lng] -> Html lng main = ParentNode "" {-# INLINE main #-} -- | Generates an HTML @\@ element with the given attributes and contents. map :: [Attribute] -> [Html lng] -> Html lng map = ParentNode "" {-# INLINE map #-} -- | Generates an HTML @\@ element with the given attributes and contents. mark :: [Attribute] -> [Html lng] -> Html lng mark = ParentNode "" {-# INLINE mark #-} -- | Generates an HTML @\@ element with the given attributes and contents. menu :: [Attribute] -> [Html lng] -> Html lng menu = ParentNode "" {-# INLINE menu #-} -- | Generates an HTML @\@ element with the given attributes. meta :: [Attribute] -> Html lng meta = LeafNode "@ element with the given attributes and contents. meter :: [Attribute] -> [Html lng] -> Html lng meter = ParentNode "" {-# INLINE meter #-} -- | Generates an HTML @\@ element with the given attributes and contents. nav :: [Attribute] -> [Html lng] -> Html lng nav = ParentNode "" {-# INLINE nav #-} -- | Generates an HTML @\@ element with the given attributes and contents. noscript :: [Attribute] -> [Html lng] -> Html lng noscript = ParentNode "" {-# INLINE noscript #-} -- | Generates an HTML @\@ element with the given attributes and contents. object :: [Attribute] -> [Html lng] -> Html lng object = ParentNode "" {-# INLINE object #-} -- | Generates an HTML @\@ element with the given attributes and contents. ol :: [Attribute] -> [Html lng] -> Html lng ol = ParentNode "" {-# INLINE ol #-} -- | Generates an HTML @\@ element with the given attributes and contents. optgroup :: [Attribute] -> [Html lng] -> Html lng optgroup = ParentNode "" {-# INLINE optgroup #-} -- | Generates an HTML @\@ element with the given attributes and contents. option :: [Attribute] -> [Html lng] -> Html lng option = ParentNode "" {-# INLINE option #-} -- | Generates an HTML @\@ element with the given attributes and contents. output :: [Attribute] -> [Html lng] -> Html lng output = ParentNode "" {-# INLINE output #-} -- | Generates an HTML @\@ element with the given attributes and contents. p :: [Attribute] -> [Html lng] -> Html lng p = ParentNode "" {-# INLINE p #-} -- | Generates an HTML @\@ element with the given attributes and contents. picture :: [Attribute] -> [Html lng] -> Html lng picture = ParentNode "" {-# INLINE picture #-} -- | Generates an HTML @\@ element with the given attributes and contents. pre :: [Attribute] -> [Html lng] -> Html lng pre = ParentNode "" {-# INLINE pre #-} -- | Generates an HTML @\@ element with the given attributes and contents. progress :: [Attribute] -> [Html lng] -> Html lng progress = ParentNode "" {-# INLINE progress #-} -- | Generates an HTML @\@ element with the given attributes and contents. q :: [Attribute] -> [Html lng] -> Html lng q = ParentNode "" {-# INLINE q #-} -- | Generates an HTML @\@ element with the given attributes and contents. rp :: [Attribute] -> [Html lng] -> Html lng rp = ParentNode "" {-# INLINE rp #-} -- | Generates an HTML @\@ element with the given attributes and contents. rt :: [Attribute] -> [Html lng] -> Html lng rt = ParentNode "" {-# INLINE rt #-} -- | Generates an HTML @\@ element with the given attributes and contents. ruby :: [Attribute] -> [Html lng] -> Html lng ruby = ParentNode "" {-# INLINE ruby #-} -- | Generates an HTML @\@ element with the given attributes and contents. s :: [Attribute] -> [Html lng] -> Html lng s = ParentNode "" {-# INLINE s #-} -- | Generates an HTML @\@ element with the given attributes and contents. samp :: [Attribute] -> [Html lng] -> Html lng samp = ParentNode "" {-# INLINE samp #-} -- | Generates an HTML @\@ element with the given attributes and contents. script :: [Attribute] -> [Html lng] -> Html lng script = ParentNode "" {-# INLINE script #-} -- | Generates an HTML @\@ element with the given attributes and contents. section :: [Attribute] -> [Html lng] -> Html lng section = ParentNode "" {-# INLINE section #-} -- | Generates an HTML @\@ element with the given attributes and contents. select :: [Attribute] -> [Html lng] -> Html lng select = ParentNode "" {-# INLINE select #-} -- | Generates an HTML @\@ element with the given attributes and contents. slot :: [Attribute] -> [Html lng] -> Html lng slot = ParentNode "" {-# INLINE slot #-} -- | Generates an HTML @\@ element with the given attributes and contents. small :: [Attribute] -> [Html lng] -> Html lng small = ParentNode "" {-# INLINE small #-} -- | Generates an HTML @\@ element with the given attributes. source :: [Attribute] -> Html lng source = LeafNode "@ element with the given attributes and contents. span :: [Attribute] -> [Html lng] -> Html lng span = ParentNode "" {-# INLINE span #-} -- | Generates an HTML @\@ element with the given attributes and contents. strong :: [Attribute] -> [Html lng] -> Html lng strong = ParentNode "" {-# INLINE strong #-} -- | Generates an HTML @\@ element with the given attributes and contents. style :: [Attribute] -> [Html lng] -> Html lng style = ParentNode "" {-# INLINE style #-} -- | Generates an HTML @\@ element with the given attributes and contents. sub :: [Attribute] -> [Html lng] -> Html lng sub = ParentNode "" {-# INLINE sub #-} -- | Generates an HTML @\@ element with the given attributes and contents. summary :: [Attribute] -> [Html lng] -> Html lng summary = ParentNode "" {-# INLINE summary #-} -- | Generates an HTML @\@ element with the given attributes and contents. sup :: [Attribute] -> [Html lng] -> Html lng sup = ParentNode "" {-# INLINE sup #-} -- | Generates an HTML @\@ element with the given attributes and contents. table :: [Attribute] -> [Html lng] -> Html lng table = ParentNode "" {-# INLINE table #-} -- | Generates an HTML @\@ element with the given attributes and contents. tbody :: [Attribute] -> [Html lng] -> Html lng tbody = ParentNode "" {-# INLINE tbody #-} -- | Generates an HTML @\@ element with the given attributes and contents. td :: [Attribute] -> [Html lng] -> Html lng td = ParentNode "" {-# INLINE td #-} -- | Generates an HTML @\@ element with the given attributes and contents. template :: [Attribute] -> [Html lng] -> Html lng template = ParentNode "" {-# INLINE template #-} -- | Generates an HTML @\@ element with the given attributes and contents. textarea :: [Attribute] -> [Html lng] -> Html lng textarea = ParentNode "" {-# INLINE textarea #-} -- | Generates an HTML @\@ element with the given attributes and contents. tfoot :: [Attribute] -> [Html lng] -> Html lng tfoot = ParentNode "" {-# INLINE tfoot #-} -- | Generates an HTML @\@ element with the given attributes and contents. th :: [Attribute] -> [Html lng] -> Html lng th = ParentNode "" {-# INLINE th #-} -- | Generates an HTML @\@ element with the given attributes and contents. thead :: [Attribute] -> [Html lng] -> Html lng thead = ParentNode "" {-# INLINE thead #-} -- | Generates an HTML @\@ element with the given attributes and contents. time :: [Attribute] -> [Html lng] -> Html lng time = ParentNode "" {-# INLINE time #-} -- | Generates an HTML @\@ element with the given attributes and contents. title :: [Attribute] -> [Html lng] -> Html lng title = ParentNode "" {-# INLINE title #-} -- | Generates an HTML @\@ element with the given attributes and contents. tr :: [Attribute] -> [Html lng] -> Html lng tr = ParentNode "" {-# INLINE tr #-} -- | Generates an HTML @\@ element with the given attributes. track :: [Attribute] -> Html lng track = LeafNode "@ element with the given attributes and contents. u :: [Attribute] -> [Html lng] -> Html lng u = ParentNode "" {-# INLINE u #-} -- | Generates an HTML @\@ element with the given attributes and contents. ul :: [Attribute] -> [Html lng] -> Html lng ul = ParentNode "" {-# INLINE ul #-} -- | Generates an HTML @\@ element with the given attributes and contents. var :: [Attribute] -> [Html lng] -> Html lng var = ParentNode "" {-# INLINE var #-} -- | Generates an HTML @\@ element with the given attributes and contents. video :: [Attribute] -> [Html lng] -> Html lng video = ParentNode "" {-# INLINE video #-} -- | Generates an HTML @\@ element with the given attributes. wbr :: [Attribute] -> Html lng wbr = LeafNode "