-- | Composite constructors and constants. module Text.HTML.Light.Composite where import Data.Char import Data.List as L import Data.Maybe import Text.HTML.Light.Attribute import Text.HTML.Light.Element import Text.XML.Light -- * Attributes -- | Variant on 'add_attrs' lifted to 'Content'. add_attrs_c :: [Attr] -> Content -> Content add_attrs_c z c = case c of Elem e -> Elem (add_attrs z e) _ -> error "add_attrs_c: not Elem" -- * Meta elements -- | Set @content-type@. meta_content_type :: String -> Content meta_content_type t = meta [http_equiv "content-type",content t] -- | Set @author@. meta_author :: String -> Content meta_author au = meta [name "author",content au] -- | Set @description@. meta_description :: String -> Content meta_description dsc = meta [name "description",content dsc] -- | Set @meta_viewport@. meta_viewport :: String -> Content meta_viewport v = meta [name "viewport",content v] -- * Link elements -- | Enumeration of HTML5 link types. data Link_Type = Link_Alternate | Link_Author | Link_Bookmark | Link_Help | Link_Icon | Link_License | Link_Next | Link_NoFollow | Link_NoReferrer | Link_Prefetch | Link_Prev | Link_Search | Link_Stylesheet deriving (Eq,Show) -- | HTML name for 'Link_Type'. -- -- > link_type_str Link_Stylesheet == "stylesheet" link_type_str :: Link_Type -> String link_type_str = L.map toLower . fromJust . stripPrefix "Link_" . show -- | Variant on 'link' with enumerated /type/ value. link_ty :: Link_Type -> [Attr] -> Content link_ty ty = link . (:) (rel (link_type_str ty)) -- | Set CSS @stylesheet@ for given @media@. link_css :: String -> String -> Content link_css m c = link_ty Link_Stylesheet [type' "text/css" ,media m ,href c] -- | Set RSS @alternate@ with given @title@. link_rss :: String -> String -> Content link_rss tt ln = link_ty Link_Alternate [type' "application/rss+xml" ,title' tt ,href ln] -- * Script elements -- | Embed javascript. script_js :: String -> Content script_js s = script [type' "text/javascript"] [cdata_raw s] -- | Source javascript. script_js_src :: FilePath -> Content script_js_src fn = script [type' "text/javascript",src fn] [] -- * Validators -- | @W3.org@ HTML validator. w3_html_validator :: String w3_html_validator = "http://validator.w3.org/check/referer" -- | @W3.org@ CSS validator. w3_css_validator :: String w3_css_validator = "http://jigsaw.w3.org/css-validator/check/referer" -- | @W3.org@ CSS validator. -- -- > w3_rss_validator "http://haskell.org" w3_rss_validator :: String -> String w3_rss_validator = (++) "http://validator.w3.org/feed/check.cgi?url=" -- * Input elements -- | Enumeration of HTML5 input types. data Input_Type = Hidden | Text | Search | Tel | Url | Email | Password | DateTime | Date | Month | Week | Time | DateTime_Local | Number | Range | Color | Checkbox | Radio | File | Submit | Image | Reset | Button deriving (Eq,Show) -- | HTML name for 'Input_Type'. input_type_str :: Input_Type -> String input_type_str = let f c = if c == '_' then '-' else c in L.map (f . toLower) . show -- | Variant on 'input' with enumerated /type/ value. input_ty :: Input_Type -> [Attr] -> Content input_ty ty = input . (:) (type' (input_type_str ty)) -- | 'Hidden' input with /name/ and /value/. input_hidden :: String -> String -> Content input_hidden k v = input_ty Hidden [name k,value v] -- | 'Submit' input with /name/ and /value/. input_submit :: String -> String -> Content input_submit k v = input_ty Submit [name k,value v]