{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} -- | -- Module : Text.CHXHtml.XHtml1_strict -- Copyright : (c) Paul Talaga 2010, -- -- License : BSD-style -- -- Maintainer : paul@fuzzpault.com -- Stability : experimental -- Portability : portable -- Description : CHXHtml (Compliant Haskell XHtml) produces W3C valid XHTML1 strict content in most cases* by building a datastructure based on the DTD. Nesting and allowed tags are controlled by recursive types. -- To simplify usage, type classes are used to substitute the corret constructor for the given context, or throw a type error if the tag is not allowed in that context. -- As a result, a single function exists per tag as well as attribute names. -- -- Each tag has two variants, one with and one without parameters, specified as @_{tag} [{children tags}]@ or @{tag}_ [{attributes}] [{children tags}]@. -- Underscores prevents namespace conflicts with @Prelude@ as well as cleaning up the syntax otherwise present using imported qualified. -- -- Textual data is entered with the function @pcdata "String"@ wherever pcdata is allowed. pcdata is HTML excaped for safety. -- For speed the variant @pcdata_bs "Data.ByteString"@ can be used which bypasses excaping. -- -- Attributes are specified by the functions @{attribute name}_att@, followed by its value of the correct type. See below for specifics. -- For W3C compliance only the last attribute will be used if duplicate names exist. -- -- Rendering to a "String" is done with the 'render' function, or to a "Data.ByteString" via the 'render_bs' function. Note that "Data.ByteString" is significatly faster than Strings. -- -- Under the hood we use a myriad of datatypes for tags and attributes whos details have been omitted below for brevity. To assist in selecting allowed tags and attributes -- 'htmlHelp' is provided which produces allowed children and attributes given a tag's nesting position. See 'htmlHelp' below for usage. -- -- \*Note we do not enforce tag ordering as described in the DTD. -- module Text.CHXHtml.XHtml1_strict( -- * Tag & Attribute Help htmlHelp, -- * Rendering render, render_bs, -- * Tags pcdata, _html, html_,_a ,a_ ,_abbr ,abbr_ ,_acronym ,acronym_ ,_address ,address_ ,_area ,area_ ,_b ,b_ ,_base ,base_ ,_bdo ,bdo_ ,_big ,big_ ,_blockquote ,blockquote_ ,_body ,body_ ,_br ,br_ ,_button ,button_ ,_caption ,caption_ ,_cite ,cite_ ,_code ,code_ ,_col ,col_ ,_colgroup ,colgroup_ ,_dd ,dd_ ,_del ,del_ ,_dfn ,dfn_ ,_div ,div_ ,_dl ,dl_ ,_dt ,dt_ ,_em ,em_ ,_fieldset ,fieldset_ ,_form ,form_ ,_h1 ,h1_ ,_h2 ,h2_ ,_h3 ,h3_ ,_h4 ,h4_ ,_h5 ,h5_ ,_h6 ,h6_ ,_head ,head_ ,_hr ,hr_ ,_i ,i_ ,_img ,img_ ,_input ,input_ ,_ins ,ins_ ,_kbd ,kbd_ ,_label ,label_ ,_legend ,legend_ ,_li ,li_ ,_link ,link_ ,_map ,map_ ,_meta ,meta_ ,_noscript ,noscript_ ,_object ,object_ ,_ol ,ol_ ,_optgroup ,optgroup_ ,_option ,option_ ,_p ,p_ ,_param ,param_ ,_pre ,pre_ ,_q ,q_ ,_samp ,samp_ ,_script ,script_ ,_select ,select_ ,_small ,small_ ,_span ,span_ ,_strong ,strong_ ,_style ,style_ ,_sub ,sub_ ,_sup ,sup_ ,_table ,table_ ,_tbody ,tbody_ ,_td ,td_ ,_textarea ,textarea_ ,_tfoot ,tfoot_ ,_th ,th_ ,_thead ,thead_ ,_title ,title_ ,_tr ,tr_ ,_tt ,tt_ ,_ul ,ul_ ,_var ,var_ , -- * Attributes http_equiv_att, http_equiv_att_bs,content_att, content_att_bs,nohref_att, onkeydown_att, onkeydown_att_bs,onkeyup_att, onkeyup_att_bs,onreset_att, onreset_att_bs,onmouseup_att, onmouseup_att_bs,scope_att, onmouseover_att, onmouseover_att_bs,align_att, lang_att, lang_att_bs,valign_att, name_att, name_att_bs,charset_att, charset_att_bs,scheme_att, scheme_att_bs,accept_charset_att, accept_charset_att_bs,onmousedown_att, onmousedown_att_bs,rev_att, rev_att_bs,span_att, span_att_bs,title_att, title_att_bs,onclick_att, onclick_att_bs,width_att, width_att_bs,enctype_att, enctype_att_bs,ismap_att, usemap_att, usemap_att_bs,coords_att, coords_att_bs,frame_att, size_att, size_att_bs,onblur_att, onblur_att_bs,datetime_att, datetime_att_bs,dir_att, summary_att, summary_att_bs,method_att, standby_att, standby_att_bs,tabindex_att, tabindex_att_bs,style_att, style_att_bs,onmousemove_att, onmousemove_att_bs,height_att, height_att_bs,codetype_att, codetype_att_bs,char_att, char_att_bs,multiple_att, codebase_att, codebase_att_bs,xmlns_att, xmlns_att_bs,profile_att, profile_att_bs,rel_att, rel_att_bs,onsubmit_att, onsubmit_att_bs,ondblclick_att, ondblclick_att_bs,axis_att, axis_att_bs,cols_att, cols_att_bs,abbr_att, abbr_att_bs,onchange_att, onchange_att_bs,readonly_att, href_att, href_att_bs,media_att, media_att_bs,id_att, id_att_bs,for_att, for_att_bs,src_att, src_att_bs,value_att, value_att_bs,data_att, data_att_bs,hreflang_att, hreflang_att_bs,checked_att, declare_att, onkeypress_att, onkeypress_att_bs,label_att, label_att_bs,class_att, class_att_bs,type_att, shape_att, accesskey_att, accesskey_att_bs,headers_att, headers_att_bs,disabled_att, rules_att, rows_att, rows_att_bs,onfocus_att, onfocus_att_bs,colspan_att, colspan_att_bs,rowspan_att, rowspan_att_bs,defer_att, cellspacing_att, cellspacing_att_bs,charoff_att, charoff_att_bs,cite_att, cite_att_bs,maxlength_att, maxlength_att_bs,onselect_att, onselect_att_bs,accept_att, accept_att_bs,archive_att, archive_att_bs,alt_att, alt_att_bs,classid_att, classid_att_bs,longdesc_att, longdesc_att_bs,onmouseout_att, onmouseout_att_bs,space_att, border_att, border_att_bs,onunload_att, onunload_att_bs,onload_att, onload_att_bs,action_att, action_att_bs,cellpadding_att, cellpadding_att_bs,valuetype_att, selected_att, -- ** Enumerated Attribute Values ValuetypeEnum(..),RulesEnum(..),ShapeEnum(..),MethodEnum(..),DirEnum(..),FrameEnum(..),ValignEnum(..),AlignEnum(..),ScopeEnum(..), ) where import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy.UTF8 as U import Data.List (nubBy,sort) import Data.Char -- Bytestring conversion functions s2b_escape = U.fromString . stringToHtmlString stringToHtmlString = concatMap fixChar where fixChar '<' = "<" fixChar '>' = ">" fixChar '&' = "&" fixChar '"' = """ fixChar c = [c] html_escape c = c s2b = U.fromString lt_byte = s2b "<" gt_byte = s2b ">" gts_byte = s2b " />" -- | HTML document root type data Ent = Html [Att0] [Ent0] deriving (Show) data Att44 = Id_Att_44 B.ByteString | Class_Att_44 B.ByteString | Style_Att_44 B.ByteString | Title_Att_44 B.ByteString | Lang_Att_44 B.ByteString | Dir_Att_44 B.ByteString | Onclick_Att_44 B.ByteString | Ondblclick_Att_44 B.ByteString | Onmousedown_Att_44 B.ByteString | Onmouseup_Att_44 B.ByteString | Onmouseover_Att_44 B.ByteString | Onmousemove_Att_44 B.ByteString | Onmouseout_Att_44 B.ByteString | Onkeypress_Att_44 B.ByteString | Onkeydown_Att_44 B.ByteString | Onkeyup_Att_44 B.ByteString | Abbr_Att_44 B.ByteString | Axis_Att_44 B.ByteString | Headers_Att_44 B.ByteString | Scope_Att_44 B.ByteString | Rowspan_Att_44 B.ByteString | Colspan_Att_44 B.ByteString | Align_Att_44 B.ByteString | Char_Att_44 B.ByteString | Charoff_Att_44 B.ByteString | Valign_Att_44 B.ByteString deriving (Show) data Att43 = Id_Att_43 B.ByteString | Class_Att_43 B.ByteString | Style_Att_43 B.ByteString | Title_Att_43 B.ByteString | Lang_Att_43 B.ByteString | Dir_Att_43 B.ByteString | Onclick_Att_43 B.ByteString | Ondblclick_Att_43 B.ByteString | Onmousedown_Att_43 B.ByteString | Onmouseup_Att_43 B.ByteString | Onmouseover_Att_43 B.ByteString | Onmousemove_Att_43 B.ByteString | Onmouseout_Att_43 B.ByteString | Onkeypress_Att_43 B.ByteString | Onkeydown_Att_43 B.ByteString | Onkeyup_Att_43 B.ByteString | Span_Att_43 B.ByteString | Width_Att_43 B.ByteString | Align_Att_43 B.ByteString | Char_Att_43 B.ByteString | Charoff_Att_43 B.ByteString | Valign_Att_43 B.ByteString deriving (Show) data Att42 = Id_Att_42 B.ByteString | Class_Att_42 B.ByteString | Style_Att_42 B.ByteString | Title_Att_42 B.ByteString | Lang_Att_42 B.ByteString | Dir_Att_42 B.ByteString | Onclick_Att_42 B.ByteString | Ondblclick_Att_42 B.ByteString | Onmousedown_Att_42 B.ByteString | Onmouseup_Att_42 B.ByteString | Onmouseover_Att_42 B.ByteString | Onmousemove_Att_42 B.ByteString | Onmouseout_Att_42 B.ByteString | Onkeypress_Att_42 B.ByteString | Onkeydown_Att_42 B.ByteString | Onkeyup_Att_42 B.ByteString | Align_Att_42 B.ByteString | Char_Att_42 B.ByteString | Charoff_Att_42 B.ByteString | Valign_Att_42 B.ByteString deriving (Show) data Att41 = Id_Att_41 B.ByteString | Class_Att_41 B.ByteString | Style_Att_41 B.ByteString | Title_Att_41 B.ByteString | Lang_Att_41 B.ByteString | Dir_Att_41 B.ByteString | Onclick_Att_41 B.ByteString | Ondblclick_Att_41 B.ByteString | Onmousedown_Att_41 B.ByteString | Onmouseup_Att_41 B.ByteString | Onmouseover_Att_41 B.ByteString | Onmousemove_Att_41 B.ByteString | Onmouseout_Att_41 B.ByteString | Onkeypress_Att_41 B.ByteString | Onkeydown_Att_41 B.ByteString | Onkeyup_Att_41 B.ByteString | Summary_Att_41 B.ByteString | Width_Att_41 B.ByteString | Border_Att_41 B.ByteString | Frame_Att_41 B.ByteString | Rules_Att_41 B.ByteString | Cellspacing_Att_41 B.ByteString | Cellpadding_Att_41 B.ByteString deriving (Show) data Att40 = Id_Att_40 B.ByteString | Class_Att_40 B.ByteString | Style_Att_40 B.ByteString | Title_Att_40 B.ByteString | Lang_Att_40 B.ByteString | Dir_Att_40 B.ByteString | Onclick_Att_40 B.ByteString | Ondblclick_Att_40 B.ByteString | Onmousedown_Att_40 B.ByteString | Onmouseup_Att_40 B.ByteString | Onmouseover_Att_40 B.ByteString | Onmousemove_Att_40 B.ByteString | Onmouseout_Att_40 B.ByteString | Onkeypress_Att_40 B.ByteString | Onkeydown_Att_40 B.ByteString | Onkeyup_Att_40 B.ByteString | Accesskey_Att_40 B.ByteString | Tabindex_Att_40 B.ByteString | Onfocus_Att_40 B.ByteString | Onblur_Att_40 B.ByteString | Name_Att_40 B.ByteString | Value_Att_40 B.ByteString | Type_Att_40 B.ByteString | Disabled_Att_40 B.ByteString deriving (Show) data Att39 = Id_Att_39 B.ByteString | Class_Att_39 B.ByteString | Style_Att_39 B.ByteString | Title_Att_39 B.ByteString | Lang_Att_39 B.ByteString | Dir_Att_39 B.ByteString | Onclick_Att_39 B.ByteString | Ondblclick_Att_39 B.ByteString | Onmousedown_Att_39 B.ByteString | Onmouseup_Att_39 B.ByteString | Onmouseover_Att_39 B.ByteString | Onmousemove_Att_39 B.ByteString | Onmouseout_Att_39 B.ByteString | Onkeypress_Att_39 B.ByteString | Onkeydown_Att_39 B.ByteString | Onkeyup_Att_39 B.ByteString | Accesskey_Att_39 B.ByteString deriving (Show) data Att38 = Cols_Att_38 B.ByteString deriving (Show) data Att37 = Rows_Att_37 B.ByteString deriving (Show) data Att36 = Id_Att_36 B.ByteString | Class_Att_36 B.ByteString | Style_Att_36 B.ByteString | Title_Att_36 B.ByteString | Lang_Att_36 B.ByteString | Dir_Att_36 B.ByteString | Onclick_Att_36 B.ByteString | Ondblclick_Att_36 B.ByteString | Onmousedown_Att_36 B.ByteString | Onmouseup_Att_36 B.ByteString | Onmouseover_Att_36 B.ByteString | Onmousemove_Att_36 B.ByteString | Onmouseout_Att_36 B.ByteString | Onkeypress_Att_36 B.ByteString | Onkeydown_Att_36 B.ByteString | Onkeyup_Att_36 B.ByteString | Accesskey_Att_36 B.ByteString | Tabindex_Att_36 B.ByteString | Onfocus_Att_36 B.ByteString | Onblur_Att_36 B.ByteString | Name_Att_36 B.ByteString | Rows_Att_36 B.ByteString | Cols_Att_36 B.ByteString | Disabled_Att_36 B.ByteString | Readonly_Att_36 B.ByteString | Onselect_Att_36 B.ByteString | Onchange_Att_36 B.ByteString deriving (Show) data Att35 = Id_Att_35 B.ByteString | Class_Att_35 B.ByteString | Style_Att_35 B.ByteString | Title_Att_35 B.ByteString | Lang_Att_35 B.ByteString | Dir_Att_35 B.ByteString | Onclick_Att_35 B.ByteString | Ondblclick_Att_35 B.ByteString | Onmousedown_Att_35 B.ByteString | Onmouseup_Att_35 B.ByteString | Onmouseover_Att_35 B.ByteString | Onmousemove_Att_35 B.ByteString | Onmouseout_Att_35 B.ByteString | Onkeypress_Att_35 B.ByteString | Onkeydown_Att_35 B.ByteString | Onkeyup_Att_35 B.ByteString | Selected_Att_35 B.ByteString | Disabled_Att_35 B.ByteString | Label_Att_35 B.ByteString | Value_Att_35 B.ByteString deriving (Show) data Att34 = Label_Att_34 B.ByteString deriving (Show) data Att33 = Id_Att_33 B.ByteString | Class_Att_33 B.ByteString | Style_Att_33 B.ByteString | Title_Att_33 B.ByteString | Lang_Att_33 B.ByteString | Dir_Att_33 B.ByteString | Onclick_Att_33 B.ByteString | Ondblclick_Att_33 B.ByteString | Onmousedown_Att_33 B.ByteString | Onmouseup_Att_33 B.ByteString | Onmouseover_Att_33 B.ByteString | Onmousemove_Att_33 B.ByteString | Onmouseout_Att_33 B.ByteString | Onkeypress_Att_33 B.ByteString | Onkeydown_Att_33 B.ByteString | Onkeyup_Att_33 B.ByteString | Disabled_Att_33 B.ByteString | Label_Att_33 B.ByteString deriving (Show) data Att32 = Id_Att_32 B.ByteString | Class_Att_32 B.ByteString | Style_Att_32 B.ByteString | Title_Att_32 B.ByteString | Lang_Att_32 B.ByteString | Dir_Att_32 B.ByteString | Onclick_Att_32 B.ByteString | Ondblclick_Att_32 B.ByteString | Onmousedown_Att_32 B.ByteString | Onmouseup_Att_32 B.ByteString | Onmouseover_Att_32 B.ByteString | Onmousemove_Att_32 B.ByteString | Onmouseout_Att_32 B.ByteString | Onkeypress_Att_32 B.ByteString | Onkeydown_Att_32 B.ByteString | Onkeyup_Att_32 B.ByteString | Name_Att_32 B.ByteString | Size_Att_32 B.ByteString | Multiple_Att_32 B.ByteString | Disabled_Att_32 B.ByteString | Tabindex_Att_32 B.ByteString | Onfocus_Att_32 B.ByteString | Onblur_Att_32 B.ByteString | Onchange_Att_32 B.ByteString deriving (Show) data Att31 = Id_Att_31 B.ByteString | Class_Att_31 B.ByteString | Style_Att_31 B.ByteString | Title_Att_31 B.ByteString | Lang_Att_31 B.ByteString | Dir_Att_31 B.ByteString | Onclick_Att_31 B.ByteString | Ondblclick_Att_31 B.ByteString | Onmousedown_Att_31 B.ByteString | Onmouseup_Att_31 B.ByteString | Onmouseover_Att_31 B.ByteString | Onmousemove_Att_31 B.ByteString | Onmouseout_Att_31 B.ByteString | Onkeypress_Att_31 B.ByteString | Onkeydown_Att_31 B.ByteString | Onkeyup_Att_31 B.ByteString | Accesskey_Att_31 B.ByteString | Tabindex_Att_31 B.ByteString | Onfocus_Att_31 B.ByteString | Onblur_Att_31 B.ByteString | Type_Att_31 B.ByteString | Name_Att_31 B.ByteString | Value_Att_31 B.ByteString | Checked_Att_31 B.ByteString | Disabled_Att_31 B.ByteString | Readonly_Att_31 B.ByteString | Size_Att_31 B.ByteString | Maxlength_Att_31 B.ByteString | Src_Att_31 B.ByteString | Alt_Att_31 B.ByteString | Usemap_Att_31 B.ByteString | Onselect_Att_31 B.ByteString | Onchange_Att_31 B.ByteString | Accept_Att_31 B.ByteString deriving (Show) data Att30 = Id_Att_30 B.ByteString | Class_Att_30 B.ByteString | Style_Att_30 B.ByteString | Title_Att_30 B.ByteString | Lang_Att_30 B.ByteString | Dir_Att_30 B.ByteString | Onclick_Att_30 B.ByteString | Ondblclick_Att_30 B.ByteString | Onmousedown_Att_30 B.ByteString | Onmouseup_Att_30 B.ByteString | Onmouseover_Att_30 B.ByteString | Onmousemove_Att_30 B.ByteString | Onmouseout_Att_30 B.ByteString | Onkeypress_Att_30 B.ByteString | Onkeydown_Att_30 B.ByteString | Onkeyup_Att_30 B.ByteString | For_Att_30 B.ByteString | Accesskey_Att_30 B.ByteString | Onfocus_Att_30 B.ByteString | Onblur_Att_30 B.ByteString deriving (Show) data Att29 = Action_Att_29 B.ByteString deriving (Show) data Att28 = Id_Att_28 B.ByteString | Class_Att_28 B.ByteString | Style_Att_28 B.ByteString | Title_Att_28 B.ByteString | Lang_Att_28 B.ByteString | Dir_Att_28 B.ByteString | Onclick_Att_28 B.ByteString | Ondblclick_Att_28 B.ByteString | Onmousedown_Att_28 B.ByteString | Onmouseup_Att_28 B.ByteString | Onmouseover_Att_28 B.ByteString | Onmousemove_Att_28 B.ByteString | Onmouseout_Att_28 B.ByteString | Onkeypress_Att_28 B.ByteString | Onkeydown_Att_28 B.ByteString | Onkeyup_Att_28 B.ByteString | Action_Att_28 B.ByteString | Method_Att_28 B.ByteString | Enctype_Att_28 B.ByteString | Onsubmit_Att_28 B.ByteString | Onreset_Att_28 B.ByteString | Accept_Att_28 B.ByteString | Accept_charset_Att_28 B.ByteString deriving (Show) data Att27 = Id_Att_27 B.ByteString | Class_Att_27 B.ByteString | Style_Att_27 B.ByteString | Title_Att_27 B.ByteString | Lang_Att_27 B.ByteString | Dir_Att_27 B.ByteString | Onclick_Att_27 B.ByteString | Ondblclick_Att_27 B.ByteString | Onmousedown_Att_27 B.ByteString | Onmouseup_Att_27 B.ByteString | Onmouseover_Att_27 B.ByteString | Onmousemove_Att_27 B.ByteString | Onmouseout_Att_27 B.ByteString | Onkeypress_Att_27 B.ByteString | Onkeydown_Att_27 B.ByteString | Onkeyup_Att_27 B.ByteString | Accesskey_Att_27 B.ByteString | Tabindex_Att_27 B.ByteString | Onfocus_Att_27 B.ByteString | Onblur_Att_27 B.ByteString | Shape_Att_27 B.ByteString | Coords_Att_27 B.ByteString | Href_Att_27 B.ByteString | Nohref_Att_27 B.ByteString | Alt_Att_27 B.ByteString deriving (Show) data Att26 = Id_Att_26 B.ByteString deriving (Show) data Att25 = Lang_Att_25 B.ByteString | Dir_Att_25 B.ByteString | Onclick_Att_25 B.ByteString | Ondblclick_Att_25 B.ByteString | Onmousedown_Att_25 B.ByteString | Onmouseup_Att_25 B.ByteString | Onmouseover_Att_25 B.ByteString | Onmousemove_Att_25 B.ByteString | Onmouseout_Att_25 B.ByteString | Onkeypress_Att_25 B.ByteString | Onkeydown_Att_25 B.ByteString | Onkeyup_Att_25 B.ByteString | Id_Att_25 B.ByteString | Class_Att_25 B.ByteString | Style_Att_25 B.ByteString | Title_Att_25 B.ByteString | Name_Att_25 B.ByteString deriving (Show) data Att24 = Alt_Att_24 B.ByteString deriving (Show) data Att23 = Src_Att_23 B.ByteString deriving (Show) data Att22 = Id_Att_22 B.ByteString | Class_Att_22 B.ByteString | Style_Att_22 B.ByteString | Title_Att_22 B.ByteString | Lang_Att_22 B.ByteString | Dir_Att_22 B.ByteString | Onclick_Att_22 B.ByteString | Ondblclick_Att_22 B.ByteString | Onmousedown_Att_22 B.ByteString | Onmouseup_Att_22 B.ByteString | Onmouseover_Att_22 B.ByteString | Onmousemove_Att_22 B.ByteString | Onmouseout_Att_22 B.ByteString | Onkeypress_Att_22 B.ByteString | Onkeydown_Att_22 B.ByteString | Onkeyup_Att_22 B.ByteString | Src_Att_22 B.ByteString | Alt_Att_22 B.ByteString | Longdesc_Att_22 B.ByteString | Height_Att_22 B.ByteString | Width_Att_22 B.ByteString | Usemap_Att_22 B.ByteString | Ismap_Att_22 B.ByteString deriving (Show) data Att21 = Id_Att_21 B.ByteString | Name_Att_21 B.ByteString | Value_Att_21 B.ByteString | Valuetype_Att_21 B.ByteString | Type_Att_21 B.ByteString deriving (Show) data Att20 = Id_Att_20 B.ByteString | Class_Att_20 B.ByteString | Style_Att_20 B.ByteString | Title_Att_20 B.ByteString | Lang_Att_20 B.ByteString | Dir_Att_20 B.ByteString | Onclick_Att_20 B.ByteString | Ondblclick_Att_20 B.ByteString | Onmousedown_Att_20 B.ByteString | Onmouseup_Att_20 B.ByteString | Onmouseover_Att_20 B.ByteString | Onmousemove_Att_20 B.ByteString | Onmouseout_Att_20 B.ByteString | Onkeypress_Att_20 B.ByteString | Onkeydown_Att_20 B.ByteString | Onkeyup_Att_20 B.ByteString | Declare_Att_20 B.ByteString | Classid_Att_20 B.ByteString | Codebase_Att_20 B.ByteString | Data_Att_20 B.ByteString | Type_Att_20 B.ByteString | Codetype_Att_20 B.ByteString | Archive_Att_20 B.ByteString | Standby_Att_20 B.ByteString | Height_Att_20 B.ByteString | Width_Att_20 B.ByteString | Usemap_Att_20 B.ByteString | Name_Att_20 B.ByteString | Tabindex_Att_20 B.ByteString deriving (Show) data Att19 = Id_Att_19 B.ByteString | Class_Att_19 B.ByteString | Style_Att_19 B.ByteString | Title_Att_19 B.ByteString deriving (Show) data Att18 = Dir_Att_18 B.ByteString deriving (Show) data Att17 = Id_Att_17 B.ByteString | Class_Att_17 B.ByteString | Style_Att_17 B.ByteString | Title_Att_17 B.ByteString | Onclick_Att_17 B.ByteString | Ondblclick_Att_17 B.ByteString | Onmousedown_Att_17 B.ByteString | Onmouseup_Att_17 B.ByteString | Onmouseover_Att_17 B.ByteString | Onmousemove_Att_17 B.ByteString | Onmouseout_Att_17 B.ByteString | Onkeypress_Att_17 B.ByteString | Onkeydown_Att_17 B.ByteString | Onkeyup_Att_17 B.ByteString | Lang_Att_17 B.ByteString | Dir_Att_17 B.ByteString deriving (Show) data Att16 = Id_Att_16 B.ByteString | Class_Att_16 B.ByteString | Style_Att_16 B.ByteString | Title_Att_16 B.ByteString | Lang_Att_16 B.ByteString | Dir_Att_16 B.ByteString | Onclick_Att_16 B.ByteString | Ondblclick_Att_16 B.ByteString | Onmousedown_Att_16 B.ByteString | Onmouseup_Att_16 B.ByteString | Onmouseover_Att_16 B.ByteString | Onmousemove_Att_16 B.ByteString | Onmouseout_Att_16 B.ByteString | Onkeypress_Att_16 B.ByteString | Onkeydown_Att_16 B.ByteString | Onkeyup_Att_16 B.ByteString | Accesskey_Att_16 B.ByteString | Tabindex_Att_16 B.ByteString | Onfocus_Att_16 B.ByteString | Onblur_Att_16 B.ByteString | Charset_Att_16 B.ByteString | Type_Att_16 B.ByteString | Name_Att_16 B.ByteString | Href_Att_16 B.ByteString | Hreflang_Att_16 B.ByteString | Rel_Att_16 B.ByteString | Rev_Att_16 B.ByteString | Shape_Att_16 B.ByteString | Coords_Att_16 B.ByteString deriving (Show) data Att15 = Id_Att_15 B.ByteString | Class_Att_15 B.ByteString | Style_Att_15 B.ByteString | Title_Att_15 B.ByteString | Lang_Att_15 B.ByteString | Dir_Att_15 B.ByteString | Onclick_Att_15 B.ByteString | Ondblclick_Att_15 B.ByteString | Onmousedown_Att_15 B.ByteString | Onmouseup_Att_15 B.ByteString | Onmouseover_Att_15 B.ByteString | Onmousemove_Att_15 B.ByteString | Onmouseout_Att_15 B.ByteString | Onkeypress_Att_15 B.ByteString | Onkeydown_Att_15 B.ByteString | Onkeyup_Att_15 B.ByteString | Cite_Att_15 B.ByteString | Datetime_Att_15 B.ByteString deriving (Show) data Att14 = Id_Att_14 B.ByteString | Class_Att_14 B.ByteString | Style_Att_14 B.ByteString | Title_Att_14 B.ByteString | Lang_Att_14 B.ByteString | Dir_Att_14 B.ByteString | Onclick_Att_14 B.ByteString | Ondblclick_Att_14 B.ByteString | Onmousedown_Att_14 B.ByteString | Onmouseup_Att_14 B.ByteString | Onmouseover_Att_14 B.ByteString | Onmousemove_Att_14 B.ByteString | Onmouseout_Att_14 B.ByteString | Onkeypress_Att_14 B.ByteString | Onkeydown_Att_14 B.ByteString | Onkeyup_Att_14 B.ByteString | Cite_Att_14 B.ByteString deriving (Show) data Att13 = Id_Att_13 B.ByteString | Class_Att_13 B.ByteString | Style_Att_13 B.ByteString | Title_Att_13 B.ByteString | Lang_Att_13 B.ByteString | Dir_Att_13 B.ByteString | Onclick_Att_13 B.ByteString | Ondblclick_Att_13 B.ByteString | Onmousedown_Att_13 B.ByteString | Onmouseup_Att_13 B.ByteString | Onmouseover_Att_13 B.ByteString | Onmousemove_Att_13 B.ByteString | Onmouseout_Att_13 B.ByteString | Onkeypress_Att_13 B.ByteString | Onkeydown_Att_13 B.ByteString | Onkeyup_Att_13 B.ByteString | Space_Att_13 B.ByteString deriving (Show) data Att12 = Id_Att_12 B.ByteString | Class_Att_12 B.ByteString | Style_Att_12 B.ByteString | Title_Att_12 B.ByteString | Lang_Att_12 B.ByteString | Dir_Att_12 B.ByteString | Onclick_Att_12 B.ByteString | Ondblclick_Att_12 B.ByteString | Onmousedown_Att_12 B.ByteString | Onmouseup_Att_12 B.ByteString | Onmouseover_Att_12 B.ByteString | Onmousemove_Att_12 B.ByteString | Onmouseout_Att_12 B.ByteString | Onkeypress_Att_12 B.ByteString | Onkeydown_Att_12 B.ByteString | Onkeyup_Att_12 B.ByteString | Onload_Att_12 B.ByteString | Onunload_Att_12 B.ByteString deriving (Show) data Att11 = Id_Att_11 B.ByteString | Class_Att_11 B.ByteString | Style_Att_11 B.ByteString | Title_Att_11 B.ByteString | Lang_Att_11 B.ByteString | Dir_Att_11 B.ByteString | Onclick_Att_11 B.ByteString | Ondblclick_Att_11 B.ByteString | Onmousedown_Att_11 B.ByteString | Onmouseup_Att_11 B.ByteString | Onmouseover_Att_11 B.ByteString | Onmousemove_Att_11 B.ByteString | Onmouseout_Att_11 B.ByteString | Onkeypress_Att_11 B.ByteString | Onkeydown_Att_11 B.ByteString | Onkeyup_Att_11 B.ByteString deriving (Show) data Att10 = Id_Att_10 B.ByteString | Charset_Att_10 B.ByteString | Type_Att_10 B.ByteString | Src_Att_10 B.ByteString | Defer_Att_10 B.ByteString | Space_Att_10 B.ByteString deriving (Show) data Att9 = Type_Att_9 B.ByteString deriving (Show) data Att8 = Lang_Att_8 B.ByteString | Dir_Att_8 B.ByteString | Id_Att_8 B.ByteString | Type_Att_8 B.ByteString | Media_Att_8 B.ByteString | Title_Att_8 B.ByteString | Space_Att_8 B.ByteString deriving (Show) data Att7 = Id_Att_7 B.ByteString | Class_Att_7 B.ByteString | Style_Att_7 B.ByteString | Title_Att_7 B.ByteString | Lang_Att_7 B.ByteString | Dir_Att_7 B.ByteString | Onclick_Att_7 B.ByteString | Ondblclick_Att_7 B.ByteString | Onmousedown_Att_7 B.ByteString | Onmouseup_Att_7 B.ByteString | Onmouseover_Att_7 B.ByteString | Onmousemove_Att_7 B.ByteString | Onmouseout_Att_7 B.ByteString | Onkeypress_Att_7 B.ByteString | Onkeydown_Att_7 B.ByteString | Onkeyup_Att_7 B.ByteString | Charset_Att_7 B.ByteString | Href_Att_7 B.ByteString | Hreflang_Att_7 B.ByteString | Type_Att_7 B.ByteString | Rel_Att_7 B.ByteString | Rev_Att_7 B.ByteString | Media_Att_7 B.ByteString deriving (Show) data Att6 = Content_Att_6 B.ByteString deriving (Show) data Att5 = Lang_Att_5 B.ByteString | Dir_Att_5 B.ByteString | Id_Att_5 B.ByteString | Http_equiv_Att_5 B.ByteString | Name_Att_5 B.ByteString | Content_Att_5 B.ByteString | Scheme_Att_5 B.ByteString deriving (Show) data Att4 = Href_Att_4 B.ByteString deriving (Show) data Att3 = Href_Att_3 B.ByteString | Id_Att_3 B.ByteString deriving (Show) data Att2 = Lang_Att_2 B.ByteString | Dir_Att_2 B.ByteString | Id_Att_2 B.ByteString deriving (Show) data Att1 = Lang_Att_1 B.ByteString | Dir_Att_1 B.ByteString | Id_Att_1 B.ByteString | Profile_Att_1 B.ByteString deriving (Show) data Att0 = Lang_Att_0 B.ByteString | Dir_Att_0 B.ByteString | Id_Att_0 B.ByteString | Xmlns_Att_0 B.ByteString deriving (Show) data ValuetypeEnum = Data | Ref | Object instance Show ValuetypeEnum where show Text.CHXHtml.XHtml1_strict.Data="data" show Text.CHXHtml.XHtml1_strict.Ref="ref" show Text.CHXHtml.XHtml1_strict.Object="object" data RulesEnum = None | Groups | Rows | Cols | All instance Show RulesEnum where show Text.CHXHtml.XHtml1_strict.None="none" show Text.CHXHtml.XHtml1_strict.Groups="groups" show Text.CHXHtml.XHtml1_strict.Rows="rows" show Text.CHXHtml.XHtml1_strict.Cols="cols" show Text.CHXHtml.XHtml1_strict.All="all" data ShapeEnum = Rect | Circle | Poly | Default instance Show ShapeEnum where show Text.CHXHtml.XHtml1_strict.Rect="rect" show Text.CHXHtml.XHtml1_strict.Circle="circle" show Text.CHXHtml.XHtml1_strict.Poly="poly" show Text.CHXHtml.XHtml1_strict.Default="default" data MethodEnum = Get | Post instance Show MethodEnum where show Text.CHXHtml.XHtml1_strict.Get="get" show Text.CHXHtml.XHtml1_strict.Post="post" data DirEnum = Ltr | Rtl instance Show DirEnum where show Text.CHXHtml.XHtml1_strict.Ltr="ltr" show Text.CHXHtml.XHtml1_strict.Rtl="rtl" data FrameEnum = Void | Above | Below | Hsides | Lhs | Rhs | Vsides | Box | Border instance Show FrameEnum where show Text.CHXHtml.XHtml1_strict.Void="void" show Text.CHXHtml.XHtml1_strict.Above="above" show Text.CHXHtml.XHtml1_strict.Below="below" show Text.CHXHtml.XHtml1_strict.Hsides="hsides" show Text.CHXHtml.XHtml1_strict.Lhs="lhs" show Text.CHXHtml.XHtml1_strict.Rhs="rhs" show Text.CHXHtml.XHtml1_strict.Vsides="vsides" show Text.CHXHtml.XHtml1_strict.Box="box" show Text.CHXHtml.XHtml1_strict.Border="border" data ValignEnum = Top | Middle | Bottom | Baseline instance Show ValignEnum where show Text.CHXHtml.XHtml1_strict.Top="top" show Text.CHXHtml.XHtml1_strict.Middle="middle" show Text.CHXHtml.XHtml1_strict.Bottom="bottom" show Text.CHXHtml.XHtml1_strict.Baseline="baseline" data AlignEnum = Left | Center | Right | Justify | Char instance Show AlignEnum where show Text.CHXHtml.XHtml1_strict.Left="left" show Text.CHXHtml.XHtml1_strict.Center="center" show Text.CHXHtml.XHtml1_strict.Right="right" show Text.CHXHtml.XHtml1_strict.Justify="justify" show Text.CHXHtml.XHtml1_strict.Char="char" data ScopeEnum = Row | Col | Rowgroup | Colgroup instance Show ScopeEnum where show Text.CHXHtml.XHtml1_strict.Row="row" show Text.CHXHtml.XHtml1_strict.Col="col" show Text.CHXHtml.XHtml1_strict.Rowgroup="rowgroup" show Text.CHXHtml.XHtml1_strict.Colgroup="colgroup" class A_Http_equiv a where http_equiv_att :: String -> a http_equiv_att_bs :: B.ByteString -> a instance A_Http_equiv Att5 where http_equiv_att s = Http_equiv_Att_5 (s2b_escape s) http_equiv_att_bs = Http_equiv_Att_5 class A_Content a where content_att :: String -> a content_att_bs :: B.ByteString -> a instance A_Content Att6 where content_att s = Content_Att_6 (s2b_escape s) content_att_bs = Content_Att_6 instance A_Content Att5 where content_att s = Content_Att_5 (s2b_escape s) content_att_bs = Content_Att_5 class A_Nohref a where nohref_att :: String -> a instance A_Nohref Att27 where nohref_att s = Nohref_Att_27 (s2b (show s)) class A_Onkeydown a where onkeydown_att :: String -> a onkeydown_att_bs :: B.ByteString -> a instance A_Onkeydown Att44 where onkeydown_att s = Onkeydown_Att_44 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_44 instance A_Onkeydown Att43 where onkeydown_att s = Onkeydown_Att_43 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_43 instance A_Onkeydown Att42 where onkeydown_att s = Onkeydown_Att_42 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_42 instance A_Onkeydown Att41 where onkeydown_att s = Onkeydown_Att_41 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_41 instance A_Onkeydown Att40 where onkeydown_att s = Onkeydown_Att_40 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_40 instance A_Onkeydown Att39 where onkeydown_att s = Onkeydown_Att_39 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_39 instance A_Onkeydown Att36 where onkeydown_att s = Onkeydown_Att_36 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_36 instance A_Onkeydown Att35 where onkeydown_att s = Onkeydown_Att_35 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_35 instance A_Onkeydown Att33 where onkeydown_att s = Onkeydown_Att_33 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_33 instance A_Onkeydown Att32 where onkeydown_att s = Onkeydown_Att_32 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_32 instance A_Onkeydown Att31 where onkeydown_att s = Onkeydown_Att_31 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_31 instance A_Onkeydown Att30 where onkeydown_att s = Onkeydown_Att_30 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_30 instance A_Onkeydown Att28 where onkeydown_att s = Onkeydown_Att_28 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_28 instance A_Onkeydown Att27 where onkeydown_att s = Onkeydown_Att_27 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_27 instance A_Onkeydown Att25 where onkeydown_att s = Onkeydown_Att_25 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_25 instance A_Onkeydown Att22 where onkeydown_att s = Onkeydown_Att_22 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_22 instance A_Onkeydown Att20 where onkeydown_att s = Onkeydown_Att_20 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_20 instance A_Onkeydown Att17 where onkeydown_att s = Onkeydown_Att_17 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_17 instance A_Onkeydown Att16 where onkeydown_att s = Onkeydown_Att_16 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_16 instance A_Onkeydown Att15 where onkeydown_att s = Onkeydown_Att_15 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_15 instance A_Onkeydown Att14 where onkeydown_att s = Onkeydown_Att_14 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_14 instance A_Onkeydown Att13 where onkeydown_att s = Onkeydown_Att_13 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_13 instance A_Onkeydown Att12 where onkeydown_att s = Onkeydown_Att_12 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_12 instance A_Onkeydown Att11 where onkeydown_att s = Onkeydown_Att_11 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_11 instance A_Onkeydown Att7 where onkeydown_att s = Onkeydown_Att_7 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_7 class A_Onkeyup a where onkeyup_att :: String -> a onkeyup_att_bs :: B.ByteString -> a instance A_Onkeyup Att44 where onkeyup_att s = Onkeyup_Att_44 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_44 instance A_Onkeyup Att43 where onkeyup_att s = Onkeyup_Att_43 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_43 instance A_Onkeyup Att42 where onkeyup_att s = Onkeyup_Att_42 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_42 instance A_Onkeyup Att41 where onkeyup_att s = Onkeyup_Att_41 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_41 instance A_Onkeyup Att40 where onkeyup_att s = Onkeyup_Att_40 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_40 instance A_Onkeyup Att39 where onkeyup_att s = Onkeyup_Att_39 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_39 instance A_Onkeyup Att36 where onkeyup_att s = Onkeyup_Att_36 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_36 instance A_Onkeyup Att35 where onkeyup_att s = Onkeyup_Att_35 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_35 instance A_Onkeyup Att33 where onkeyup_att s = Onkeyup_Att_33 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_33 instance A_Onkeyup Att32 where onkeyup_att s = Onkeyup_Att_32 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_32 instance A_Onkeyup Att31 where onkeyup_att s = Onkeyup_Att_31 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_31 instance A_Onkeyup Att30 where onkeyup_att s = Onkeyup_Att_30 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_30 instance A_Onkeyup Att28 where onkeyup_att s = Onkeyup_Att_28 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_28 instance A_Onkeyup Att27 where onkeyup_att s = Onkeyup_Att_27 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_27 instance A_Onkeyup Att25 where onkeyup_att s = Onkeyup_Att_25 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_25 instance A_Onkeyup Att22 where onkeyup_att s = Onkeyup_Att_22 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_22 instance A_Onkeyup Att20 where onkeyup_att s = Onkeyup_Att_20 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_20 instance A_Onkeyup Att17 where onkeyup_att s = Onkeyup_Att_17 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_17 instance A_Onkeyup Att16 where onkeyup_att s = Onkeyup_Att_16 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_16 instance A_Onkeyup Att15 where onkeyup_att s = Onkeyup_Att_15 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_15 instance A_Onkeyup Att14 where onkeyup_att s = Onkeyup_Att_14 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_14 instance A_Onkeyup Att13 where onkeyup_att s = Onkeyup_Att_13 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_13 instance A_Onkeyup Att12 where onkeyup_att s = Onkeyup_Att_12 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_12 instance A_Onkeyup Att11 where onkeyup_att s = Onkeyup_Att_11 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_11 instance A_Onkeyup Att7 where onkeyup_att s = Onkeyup_Att_7 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_7 class A_Onreset a where onreset_att :: String -> a onreset_att_bs :: B.ByteString -> a instance A_Onreset Att28 where onreset_att s = Onreset_Att_28 (s2b_escape s) onreset_att_bs = Onreset_Att_28 class A_Onmouseup a where onmouseup_att :: String -> a onmouseup_att_bs :: B.ByteString -> a instance A_Onmouseup Att44 where onmouseup_att s = Onmouseup_Att_44 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_44 instance A_Onmouseup Att43 where onmouseup_att s = Onmouseup_Att_43 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_43 instance A_Onmouseup Att42 where onmouseup_att s = Onmouseup_Att_42 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_42 instance A_Onmouseup Att41 where onmouseup_att s = Onmouseup_Att_41 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_41 instance A_Onmouseup Att40 where onmouseup_att s = Onmouseup_Att_40 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_40 instance A_Onmouseup Att39 where onmouseup_att s = Onmouseup_Att_39 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_39 instance A_Onmouseup Att36 where onmouseup_att s = Onmouseup_Att_36 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_36 instance A_Onmouseup Att35 where onmouseup_att s = Onmouseup_Att_35 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_35 instance A_Onmouseup Att33 where onmouseup_att s = Onmouseup_Att_33 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_33 instance A_Onmouseup Att32 where onmouseup_att s = Onmouseup_Att_32 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_32 instance A_Onmouseup Att31 where onmouseup_att s = Onmouseup_Att_31 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_31 instance A_Onmouseup Att30 where onmouseup_att s = Onmouseup_Att_30 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_30 instance A_Onmouseup Att28 where onmouseup_att s = Onmouseup_Att_28 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_28 instance A_Onmouseup Att27 where onmouseup_att s = Onmouseup_Att_27 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_27 instance A_Onmouseup Att25 where onmouseup_att s = Onmouseup_Att_25 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_25 instance A_Onmouseup Att22 where onmouseup_att s = Onmouseup_Att_22 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_22 instance A_Onmouseup Att20 where onmouseup_att s = Onmouseup_Att_20 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_20 instance A_Onmouseup Att17 where onmouseup_att s = Onmouseup_Att_17 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_17 instance A_Onmouseup Att16 where onmouseup_att s = Onmouseup_Att_16 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_16 instance A_Onmouseup Att15 where onmouseup_att s = Onmouseup_Att_15 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_15 instance A_Onmouseup Att14 where onmouseup_att s = Onmouseup_Att_14 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_14 instance A_Onmouseup Att13 where onmouseup_att s = Onmouseup_Att_13 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_13 instance A_Onmouseup Att12 where onmouseup_att s = Onmouseup_Att_12 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_12 instance A_Onmouseup Att11 where onmouseup_att s = Onmouseup_Att_11 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_11 instance A_Onmouseup Att7 where onmouseup_att s = Onmouseup_Att_7 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_7 class A_Scope a where scope_att :: ScopeEnum -> a instance A_Scope Att44 where scope_att s = Scope_Att_44 (s2b (show s)) class A_Onmouseover a where onmouseover_att :: String -> a onmouseover_att_bs :: B.ByteString -> a instance A_Onmouseover Att44 where onmouseover_att s = Onmouseover_Att_44 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_44 instance A_Onmouseover Att43 where onmouseover_att s = Onmouseover_Att_43 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_43 instance A_Onmouseover Att42 where onmouseover_att s = Onmouseover_Att_42 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_42 instance A_Onmouseover Att41 where onmouseover_att s = Onmouseover_Att_41 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_41 instance A_Onmouseover Att40 where onmouseover_att s = Onmouseover_Att_40 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_40 instance A_Onmouseover Att39 where onmouseover_att s = Onmouseover_Att_39 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_39 instance A_Onmouseover Att36 where onmouseover_att s = Onmouseover_Att_36 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_36 instance A_Onmouseover Att35 where onmouseover_att s = Onmouseover_Att_35 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_35 instance A_Onmouseover Att33 where onmouseover_att s = Onmouseover_Att_33 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_33 instance A_Onmouseover Att32 where onmouseover_att s = Onmouseover_Att_32 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_32 instance A_Onmouseover Att31 where onmouseover_att s = Onmouseover_Att_31 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_31 instance A_Onmouseover Att30 where onmouseover_att s = Onmouseover_Att_30 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_30 instance A_Onmouseover Att28 where onmouseover_att s = Onmouseover_Att_28 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_28 instance A_Onmouseover Att27 where onmouseover_att s = Onmouseover_Att_27 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_27 instance A_Onmouseover Att25 where onmouseover_att s = Onmouseover_Att_25 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_25 instance A_Onmouseover Att22 where onmouseover_att s = Onmouseover_Att_22 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_22 instance A_Onmouseover Att20 where onmouseover_att s = Onmouseover_Att_20 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_20 instance A_Onmouseover Att17 where onmouseover_att s = Onmouseover_Att_17 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_17 instance A_Onmouseover Att16 where onmouseover_att s = Onmouseover_Att_16 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_16 instance A_Onmouseover Att15 where onmouseover_att s = Onmouseover_Att_15 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_15 instance A_Onmouseover Att14 where onmouseover_att s = Onmouseover_Att_14 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_14 instance A_Onmouseover Att13 where onmouseover_att s = Onmouseover_Att_13 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_13 instance A_Onmouseover Att12 where onmouseover_att s = Onmouseover_Att_12 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_12 instance A_Onmouseover Att11 where onmouseover_att s = Onmouseover_Att_11 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_11 instance A_Onmouseover Att7 where onmouseover_att s = Onmouseover_Att_7 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_7 class A_Align a where align_att :: AlignEnum -> a instance A_Align Att44 where align_att s = Align_Att_44 (s2b (show s)) instance A_Align Att43 where align_att s = Align_Att_43 (s2b (show s)) instance A_Align Att42 where align_att s = Align_Att_42 (s2b (show s)) class A_Lang a where lang_att :: String -> a lang_att_bs :: B.ByteString -> a instance A_Lang Att44 where lang_att s = Lang_Att_44 (s2b_escape s) lang_att_bs = Lang_Att_44 instance A_Lang Att43 where lang_att s = Lang_Att_43 (s2b_escape s) lang_att_bs = Lang_Att_43 instance A_Lang Att42 where lang_att s = Lang_Att_42 (s2b_escape s) lang_att_bs = Lang_Att_42 instance A_Lang Att41 where lang_att s = Lang_Att_41 (s2b_escape s) lang_att_bs = Lang_Att_41 instance A_Lang Att40 where lang_att s = Lang_Att_40 (s2b_escape s) lang_att_bs = Lang_Att_40 instance A_Lang Att39 where lang_att s = Lang_Att_39 (s2b_escape s) lang_att_bs = Lang_Att_39 instance A_Lang Att36 where lang_att s = Lang_Att_36 (s2b_escape s) lang_att_bs = Lang_Att_36 instance A_Lang Att35 where lang_att s = Lang_Att_35 (s2b_escape s) lang_att_bs = Lang_Att_35 instance A_Lang Att33 where lang_att s = Lang_Att_33 (s2b_escape s) lang_att_bs = Lang_Att_33 instance A_Lang Att32 where lang_att s = Lang_Att_32 (s2b_escape s) lang_att_bs = Lang_Att_32 instance A_Lang Att31 where lang_att s = Lang_Att_31 (s2b_escape s) lang_att_bs = Lang_Att_31 instance A_Lang Att30 where lang_att s = Lang_Att_30 (s2b_escape s) lang_att_bs = Lang_Att_30 instance A_Lang Att28 where lang_att s = Lang_Att_28 (s2b_escape s) lang_att_bs = Lang_Att_28 instance A_Lang Att27 where lang_att s = Lang_Att_27 (s2b_escape s) lang_att_bs = Lang_Att_27 instance A_Lang Att25 where lang_att s = Lang_Att_25 (s2b_escape s) lang_att_bs = Lang_Att_25 instance A_Lang Att22 where lang_att s = Lang_Att_22 (s2b_escape s) lang_att_bs = Lang_Att_22 instance A_Lang Att20 where lang_att s = Lang_Att_20 (s2b_escape s) lang_att_bs = Lang_Att_20 instance A_Lang Att17 where lang_att s = Lang_Att_17 (s2b_escape s) lang_att_bs = Lang_Att_17 instance A_Lang Att16 where lang_att s = Lang_Att_16 (s2b_escape s) lang_att_bs = Lang_Att_16 instance A_Lang Att15 where lang_att s = Lang_Att_15 (s2b_escape s) lang_att_bs = Lang_Att_15 instance A_Lang Att14 where lang_att s = Lang_Att_14 (s2b_escape s) lang_att_bs = Lang_Att_14 instance A_Lang Att13 where lang_att s = Lang_Att_13 (s2b_escape s) lang_att_bs = Lang_Att_13 instance A_Lang Att12 where lang_att s = Lang_Att_12 (s2b_escape s) lang_att_bs = Lang_Att_12 instance A_Lang Att11 where lang_att s = Lang_Att_11 (s2b_escape s) lang_att_bs = Lang_Att_11 instance A_Lang Att8 where lang_att s = Lang_Att_8 (s2b_escape s) lang_att_bs = Lang_Att_8 instance A_Lang Att7 where lang_att s = Lang_Att_7 (s2b_escape s) lang_att_bs = Lang_Att_7 instance A_Lang Att5 where lang_att s = Lang_Att_5 (s2b_escape s) lang_att_bs = Lang_Att_5 instance A_Lang Att2 where lang_att s = Lang_Att_2 (s2b_escape s) lang_att_bs = Lang_Att_2 instance A_Lang Att1 where lang_att s = Lang_Att_1 (s2b_escape s) lang_att_bs = Lang_Att_1 instance A_Lang Att0 where lang_att s = Lang_Att_0 (s2b_escape s) lang_att_bs = Lang_Att_0 class A_Valign a where valign_att :: ValignEnum -> a instance A_Valign Att44 where valign_att s = Valign_Att_44 (s2b (show s)) instance A_Valign Att43 where valign_att s = Valign_Att_43 (s2b (show s)) instance A_Valign Att42 where valign_att s = Valign_Att_42 (s2b (show s)) class A_Name a where name_att :: String -> a name_att_bs :: B.ByteString -> a instance A_Name Att40 where name_att s = Name_Att_40 (s2b_escape s) name_att_bs = Name_Att_40 instance A_Name Att36 where name_att s = Name_Att_36 (s2b_escape s) name_att_bs = Name_Att_36 instance A_Name Att32 where name_att s = Name_Att_32 (s2b_escape s) name_att_bs = Name_Att_32 instance A_Name Att31 where name_att s = Name_Att_31 (s2b_escape s) name_att_bs = Name_Att_31 instance A_Name Att25 where name_att s = Name_Att_25 (s2b_escape s) name_att_bs = Name_Att_25 instance A_Name Att21 where name_att s = Name_Att_21 (s2b_escape s) name_att_bs = Name_Att_21 instance A_Name Att20 where name_att s = Name_Att_20 (s2b_escape s) name_att_bs = Name_Att_20 instance A_Name Att16 where name_att s = Name_Att_16 (s2b_escape s) name_att_bs = Name_Att_16 instance A_Name Att5 where name_att s = Name_Att_5 (s2b_escape s) name_att_bs = Name_Att_5 class A_Charset a where charset_att :: String -> a charset_att_bs :: B.ByteString -> a instance A_Charset Att16 where charset_att s = Charset_Att_16 (s2b_escape s) charset_att_bs = Charset_Att_16 instance A_Charset Att10 where charset_att s = Charset_Att_10 (s2b_escape s) charset_att_bs = Charset_Att_10 instance A_Charset Att7 where charset_att s = Charset_Att_7 (s2b_escape s) charset_att_bs = Charset_Att_7 class A_Scheme a where scheme_att :: String -> a scheme_att_bs :: B.ByteString -> a instance A_Scheme Att5 where scheme_att s = Scheme_Att_5 (s2b_escape s) scheme_att_bs = Scheme_Att_5 class A_Accept_charset a where accept_charset_att :: String -> a accept_charset_att_bs :: B.ByteString -> a instance A_Accept_charset Att28 where accept_charset_att s = Accept_charset_Att_28 (s2b_escape s) accept_charset_att_bs = Accept_charset_Att_28 class A_Onmousedown a where onmousedown_att :: String -> a onmousedown_att_bs :: B.ByteString -> a instance A_Onmousedown Att44 where onmousedown_att s = Onmousedown_Att_44 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_44 instance A_Onmousedown Att43 where onmousedown_att s = Onmousedown_Att_43 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_43 instance A_Onmousedown Att42 where onmousedown_att s = Onmousedown_Att_42 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_42 instance A_Onmousedown Att41 where onmousedown_att s = Onmousedown_Att_41 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_41 instance A_Onmousedown Att40 where onmousedown_att s = Onmousedown_Att_40 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_40 instance A_Onmousedown Att39 where onmousedown_att s = Onmousedown_Att_39 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_39 instance A_Onmousedown Att36 where onmousedown_att s = Onmousedown_Att_36 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_36 instance A_Onmousedown Att35 where onmousedown_att s = Onmousedown_Att_35 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_35 instance A_Onmousedown Att33 where onmousedown_att s = Onmousedown_Att_33 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_33 instance A_Onmousedown Att32 where onmousedown_att s = Onmousedown_Att_32 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_32 instance A_Onmousedown Att31 where onmousedown_att s = Onmousedown_Att_31 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_31 instance A_Onmousedown Att30 where onmousedown_att s = Onmousedown_Att_30 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_30 instance A_Onmousedown Att28 where onmousedown_att s = Onmousedown_Att_28 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_28 instance A_Onmousedown Att27 where onmousedown_att s = Onmousedown_Att_27 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_27 instance A_Onmousedown Att25 where onmousedown_att s = Onmousedown_Att_25 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_25 instance A_Onmousedown Att22 where onmousedown_att s = Onmousedown_Att_22 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_22 instance A_Onmousedown Att20 where onmousedown_att s = Onmousedown_Att_20 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_20 instance A_Onmousedown Att17 where onmousedown_att s = Onmousedown_Att_17 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_17 instance A_Onmousedown Att16 where onmousedown_att s = Onmousedown_Att_16 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_16 instance A_Onmousedown Att15 where onmousedown_att s = Onmousedown_Att_15 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_15 instance A_Onmousedown Att14 where onmousedown_att s = Onmousedown_Att_14 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_14 instance A_Onmousedown Att13 where onmousedown_att s = Onmousedown_Att_13 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_13 instance A_Onmousedown Att12 where onmousedown_att s = Onmousedown_Att_12 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_12 instance A_Onmousedown Att11 where onmousedown_att s = Onmousedown_Att_11 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_11 instance A_Onmousedown Att7 where onmousedown_att s = Onmousedown_Att_7 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_7 class A_Rev a where rev_att :: String -> a rev_att_bs :: B.ByteString -> a instance A_Rev Att16 where rev_att s = Rev_Att_16 (s2b_escape s) rev_att_bs = Rev_Att_16 instance A_Rev Att7 where rev_att s = Rev_Att_7 (s2b_escape s) rev_att_bs = Rev_Att_7 class A_Span a where span_att :: String -> a span_att_bs :: B.ByteString -> a instance A_Span Att43 where span_att s = Span_Att_43 (s2b_escape s) span_att_bs = Span_Att_43 class A_Title a where title_att :: String -> a title_att_bs :: B.ByteString -> a instance A_Title Att44 where title_att s = Title_Att_44 (s2b_escape s) title_att_bs = Title_Att_44 instance A_Title Att43 where title_att s = Title_Att_43 (s2b_escape s) title_att_bs = Title_Att_43 instance A_Title Att42 where title_att s = Title_Att_42 (s2b_escape s) title_att_bs = Title_Att_42 instance A_Title Att41 where title_att s = Title_Att_41 (s2b_escape s) title_att_bs = Title_Att_41 instance A_Title Att40 where title_att s = Title_Att_40 (s2b_escape s) title_att_bs = Title_Att_40 instance A_Title Att39 where title_att s = Title_Att_39 (s2b_escape s) title_att_bs = Title_Att_39 instance A_Title Att36 where title_att s = Title_Att_36 (s2b_escape s) title_att_bs = Title_Att_36 instance A_Title Att35 where title_att s = Title_Att_35 (s2b_escape s) title_att_bs = Title_Att_35 instance A_Title Att33 where title_att s = Title_Att_33 (s2b_escape s) title_att_bs = Title_Att_33 instance A_Title Att32 where title_att s = Title_Att_32 (s2b_escape s) title_att_bs = Title_Att_32 instance A_Title Att31 where title_att s = Title_Att_31 (s2b_escape s) title_att_bs = Title_Att_31 instance A_Title Att30 where title_att s = Title_Att_30 (s2b_escape s) title_att_bs = Title_Att_30 instance A_Title Att28 where title_att s = Title_Att_28 (s2b_escape s) title_att_bs = Title_Att_28 instance A_Title Att27 where title_att s = Title_Att_27 (s2b_escape s) title_att_bs = Title_Att_27 instance A_Title Att25 where title_att s = Title_Att_25 (s2b_escape s) title_att_bs = Title_Att_25 instance A_Title Att22 where title_att s = Title_Att_22 (s2b_escape s) title_att_bs = Title_Att_22 instance A_Title Att20 where title_att s = Title_Att_20 (s2b_escape s) title_att_bs = Title_Att_20 instance A_Title Att19 where title_att s = Title_Att_19 (s2b_escape s) title_att_bs = Title_Att_19 instance A_Title Att17 where title_att s = Title_Att_17 (s2b_escape s) title_att_bs = Title_Att_17 instance A_Title Att16 where title_att s = Title_Att_16 (s2b_escape s) title_att_bs = Title_Att_16 instance A_Title Att15 where title_att s = Title_Att_15 (s2b_escape s) title_att_bs = Title_Att_15 instance A_Title Att14 where title_att s = Title_Att_14 (s2b_escape s) title_att_bs = Title_Att_14 instance A_Title Att13 where title_att s = Title_Att_13 (s2b_escape s) title_att_bs = Title_Att_13 instance A_Title Att12 where title_att s = Title_Att_12 (s2b_escape s) title_att_bs = Title_Att_12 instance A_Title Att11 where title_att s = Title_Att_11 (s2b_escape s) title_att_bs = Title_Att_11 instance A_Title Att8 where title_att s = Title_Att_8 (s2b_escape s) title_att_bs = Title_Att_8 instance A_Title Att7 where title_att s = Title_Att_7 (s2b_escape s) title_att_bs = Title_Att_7 class A_Onclick a where onclick_att :: String -> a onclick_att_bs :: B.ByteString -> a instance A_Onclick Att44 where onclick_att s = Onclick_Att_44 (s2b_escape s) onclick_att_bs = Onclick_Att_44 instance A_Onclick Att43 where onclick_att s = Onclick_Att_43 (s2b_escape s) onclick_att_bs = Onclick_Att_43 instance A_Onclick Att42 where onclick_att s = Onclick_Att_42 (s2b_escape s) onclick_att_bs = Onclick_Att_42 instance A_Onclick Att41 where onclick_att s = Onclick_Att_41 (s2b_escape s) onclick_att_bs = Onclick_Att_41 instance A_Onclick Att40 where onclick_att s = Onclick_Att_40 (s2b_escape s) onclick_att_bs = Onclick_Att_40 instance A_Onclick Att39 where onclick_att s = Onclick_Att_39 (s2b_escape s) onclick_att_bs = Onclick_Att_39 instance A_Onclick Att36 where onclick_att s = Onclick_Att_36 (s2b_escape s) onclick_att_bs = Onclick_Att_36 instance A_Onclick Att35 where onclick_att s = Onclick_Att_35 (s2b_escape s) onclick_att_bs = Onclick_Att_35 instance A_Onclick Att33 where onclick_att s = Onclick_Att_33 (s2b_escape s) onclick_att_bs = Onclick_Att_33 instance A_Onclick Att32 where onclick_att s = Onclick_Att_32 (s2b_escape s) onclick_att_bs = Onclick_Att_32 instance A_Onclick Att31 where onclick_att s = Onclick_Att_31 (s2b_escape s) onclick_att_bs = Onclick_Att_31 instance A_Onclick Att30 where onclick_att s = Onclick_Att_30 (s2b_escape s) onclick_att_bs = Onclick_Att_30 instance A_Onclick Att28 where onclick_att s = Onclick_Att_28 (s2b_escape s) onclick_att_bs = Onclick_Att_28 instance A_Onclick Att27 where onclick_att s = Onclick_Att_27 (s2b_escape s) onclick_att_bs = Onclick_Att_27 instance A_Onclick Att25 where onclick_att s = Onclick_Att_25 (s2b_escape s) onclick_att_bs = Onclick_Att_25 instance A_Onclick Att22 where onclick_att s = Onclick_Att_22 (s2b_escape s) onclick_att_bs = Onclick_Att_22 instance A_Onclick Att20 where onclick_att s = Onclick_Att_20 (s2b_escape s) onclick_att_bs = Onclick_Att_20 instance A_Onclick Att17 where onclick_att s = Onclick_Att_17 (s2b_escape s) onclick_att_bs = Onclick_Att_17 instance A_Onclick Att16 where onclick_att s = Onclick_Att_16 (s2b_escape s) onclick_att_bs = Onclick_Att_16 instance A_Onclick Att15 where onclick_att s = Onclick_Att_15 (s2b_escape s) onclick_att_bs = Onclick_Att_15 instance A_Onclick Att14 where onclick_att s = Onclick_Att_14 (s2b_escape s) onclick_att_bs = Onclick_Att_14 instance A_Onclick Att13 where onclick_att s = Onclick_Att_13 (s2b_escape s) onclick_att_bs = Onclick_Att_13 instance A_Onclick Att12 where onclick_att s = Onclick_Att_12 (s2b_escape s) onclick_att_bs = Onclick_Att_12 instance A_Onclick Att11 where onclick_att s = Onclick_Att_11 (s2b_escape s) onclick_att_bs = Onclick_Att_11 instance A_Onclick Att7 where onclick_att s = Onclick_Att_7 (s2b_escape s) onclick_att_bs = Onclick_Att_7 class A_Width a where width_att :: String -> a width_att_bs :: B.ByteString -> a instance A_Width Att43 where width_att s = Width_Att_43 (s2b_escape s) width_att_bs = Width_Att_43 instance A_Width Att41 where width_att s = Width_Att_41 (s2b_escape s) width_att_bs = Width_Att_41 instance A_Width Att22 where width_att s = Width_Att_22 (s2b_escape s) width_att_bs = Width_Att_22 instance A_Width Att20 where width_att s = Width_Att_20 (s2b_escape s) width_att_bs = Width_Att_20 class A_Enctype a where enctype_att :: String -> a enctype_att_bs :: B.ByteString -> a instance A_Enctype Att28 where enctype_att s = Enctype_Att_28 (s2b_escape s) enctype_att_bs = Enctype_Att_28 class A_Ismap a where ismap_att :: String -> a instance A_Ismap Att22 where ismap_att s = Ismap_Att_22 (s2b (show s)) class A_Usemap a where usemap_att :: String -> a usemap_att_bs :: B.ByteString -> a instance A_Usemap Att31 where usemap_att s = Usemap_Att_31 (s2b_escape s) usemap_att_bs = Usemap_Att_31 instance A_Usemap Att22 where usemap_att s = Usemap_Att_22 (s2b_escape s) usemap_att_bs = Usemap_Att_22 instance A_Usemap Att20 where usemap_att s = Usemap_Att_20 (s2b_escape s) usemap_att_bs = Usemap_Att_20 class A_Coords a where coords_att :: String -> a coords_att_bs :: B.ByteString -> a instance A_Coords Att27 where coords_att s = Coords_Att_27 (s2b_escape s) coords_att_bs = Coords_Att_27 instance A_Coords Att16 where coords_att s = Coords_Att_16 (s2b_escape s) coords_att_bs = Coords_Att_16 class A_Frame a where frame_att :: FrameEnum -> a instance A_Frame Att41 where frame_att s = Frame_Att_41 (s2b (show s)) class A_Size a where size_att :: String -> a size_att_bs :: B.ByteString -> a instance A_Size Att32 where size_att s = Size_Att_32 (s2b_escape s) size_att_bs = Size_Att_32 instance A_Size Att31 where size_att s = Size_Att_31 (s2b_escape s) size_att_bs = Size_Att_31 class A_Onblur a where onblur_att :: String -> a onblur_att_bs :: B.ByteString -> a instance A_Onblur Att40 where onblur_att s = Onblur_Att_40 (s2b_escape s) onblur_att_bs = Onblur_Att_40 instance A_Onblur Att36 where onblur_att s = Onblur_Att_36 (s2b_escape s) onblur_att_bs = Onblur_Att_36 instance A_Onblur Att32 where onblur_att s = Onblur_Att_32 (s2b_escape s) onblur_att_bs = Onblur_Att_32 instance A_Onblur Att31 where onblur_att s = Onblur_Att_31 (s2b_escape s) onblur_att_bs = Onblur_Att_31 instance A_Onblur Att30 where onblur_att s = Onblur_Att_30 (s2b_escape s) onblur_att_bs = Onblur_Att_30 instance A_Onblur Att27 where onblur_att s = Onblur_Att_27 (s2b_escape s) onblur_att_bs = Onblur_Att_27 instance A_Onblur Att16 where onblur_att s = Onblur_Att_16 (s2b_escape s) onblur_att_bs = Onblur_Att_16 class A_Datetime a where datetime_att :: String -> a datetime_att_bs :: B.ByteString -> a instance A_Datetime Att15 where datetime_att s = Datetime_Att_15 (s2b_escape s) datetime_att_bs = Datetime_Att_15 class A_Dir a where dir_att :: DirEnum -> a instance A_Dir Att44 where dir_att s = Dir_Att_44 (s2b (show s)) instance A_Dir Att43 where dir_att s = Dir_Att_43 (s2b (show s)) instance A_Dir Att42 where dir_att s = Dir_Att_42 (s2b (show s)) instance A_Dir Att41 where dir_att s = Dir_Att_41 (s2b (show s)) instance A_Dir Att40 where dir_att s = Dir_Att_40 (s2b (show s)) instance A_Dir Att39 where dir_att s = Dir_Att_39 (s2b (show s)) instance A_Dir Att36 where dir_att s = Dir_Att_36 (s2b (show s)) instance A_Dir Att35 where dir_att s = Dir_Att_35 (s2b (show s)) instance A_Dir Att33 where dir_att s = Dir_Att_33 (s2b (show s)) instance A_Dir Att32 where dir_att s = Dir_Att_32 (s2b (show s)) instance A_Dir Att31 where dir_att s = Dir_Att_31 (s2b (show s)) instance A_Dir Att30 where dir_att s = Dir_Att_30 (s2b (show s)) instance A_Dir Att28 where dir_att s = Dir_Att_28 (s2b (show s)) instance A_Dir Att27 where dir_att s = Dir_Att_27 (s2b (show s)) instance A_Dir Att25 where dir_att s = Dir_Att_25 (s2b (show s)) instance A_Dir Att22 where dir_att s = Dir_Att_22 (s2b (show s)) instance A_Dir Att20 where dir_att s = Dir_Att_20 (s2b (show s)) instance A_Dir Att18 where dir_att s = Dir_Att_18 (s2b (show s)) instance A_Dir Att17 where dir_att s = Dir_Att_17 (s2b (show s)) instance A_Dir Att16 where dir_att s = Dir_Att_16 (s2b (show s)) instance A_Dir Att15 where dir_att s = Dir_Att_15 (s2b (show s)) instance A_Dir Att14 where dir_att s = Dir_Att_14 (s2b (show s)) instance A_Dir Att13 where dir_att s = Dir_Att_13 (s2b (show s)) instance A_Dir Att12 where dir_att s = Dir_Att_12 (s2b (show s)) instance A_Dir Att11 where dir_att s = Dir_Att_11 (s2b (show s)) instance A_Dir Att8 where dir_att s = Dir_Att_8 (s2b (show s)) instance A_Dir Att7 where dir_att s = Dir_Att_7 (s2b (show s)) instance A_Dir Att5 where dir_att s = Dir_Att_5 (s2b (show s)) instance A_Dir Att2 where dir_att s = Dir_Att_2 (s2b (show s)) instance A_Dir Att1 where dir_att s = Dir_Att_1 (s2b (show s)) instance A_Dir Att0 where dir_att s = Dir_Att_0 (s2b (show s)) class A_Summary a where summary_att :: String -> a summary_att_bs :: B.ByteString -> a instance A_Summary Att41 where summary_att s = Summary_Att_41 (s2b_escape s) summary_att_bs = Summary_Att_41 class A_Method a where method_att :: MethodEnum -> a instance A_Method Att28 where method_att s = Method_Att_28 (s2b (show s)) class A_Standby a where standby_att :: String -> a standby_att_bs :: B.ByteString -> a instance A_Standby Att20 where standby_att s = Standby_Att_20 (s2b_escape s) standby_att_bs = Standby_Att_20 class A_Tabindex a where tabindex_att :: String -> a tabindex_att_bs :: B.ByteString -> a instance A_Tabindex Att40 where tabindex_att s = Tabindex_Att_40 (s2b_escape s) tabindex_att_bs = Tabindex_Att_40 instance A_Tabindex Att36 where tabindex_att s = Tabindex_Att_36 (s2b_escape s) tabindex_att_bs = Tabindex_Att_36 instance A_Tabindex Att32 where tabindex_att s = Tabindex_Att_32 (s2b_escape s) tabindex_att_bs = Tabindex_Att_32 instance A_Tabindex Att31 where tabindex_att s = Tabindex_Att_31 (s2b_escape s) tabindex_att_bs = Tabindex_Att_31 instance A_Tabindex Att27 where tabindex_att s = Tabindex_Att_27 (s2b_escape s) tabindex_att_bs = Tabindex_Att_27 instance A_Tabindex Att20 where tabindex_att s = Tabindex_Att_20 (s2b_escape s) tabindex_att_bs = Tabindex_Att_20 instance A_Tabindex Att16 where tabindex_att s = Tabindex_Att_16 (s2b_escape s) tabindex_att_bs = Tabindex_Att_16 class A_Style a where style_att :: String -> a style_att_bs :: B.ByteString -> a instance A_Style Att44 where style_att s = Style_Att_44 (s2b_escape s) style_att_bs = Style_Att_44 instance A_Style Att43 where style_att s = Style_Att_43 (s2b_escape s) style_att_bs = Style_Att_43 instance A_Style Att42 where style_att s = Style_Att_42 (s2b_escape s) style_att_bs = Style_Att_42 instance A_Style Att41 where style_att s = Style_Att_41 (s2b_escape s) style_att_bs = Style_Att_41 instance A_Style Att40 where style_att s = Style_Att_40 (s2b_escape s) style_att_bs = Style_Att_40 instance A_Style Att39 where style_att s = Style_Att_39 (s2b_escape s) style_att_bs = Style_Att_39 instance A_Style Att36 where style_att s = Style_Att_36 (s2b_escape s) style_att_bs = Style_Att_36 instance A_Style Att35 where style_att s = Style_Att_35 (s2b_escape s) style_att_bs = Style_Att_35 instance A_Style Att33 where style_att s = Style_Att_33 (s2b_escape s) style_att_bs = Style_Att_33 instance A_Style Att32 where style_att s = Style_Att_32 (s2b_escape s) style_att_bs = Style_Att_32 instance A_Style Att31 where style_att s = Style_Att_31 (s2b_escape s) style_att_bs = Style_Att_31 instance A_Style Att30 where style_att s = Style_Att_30 (s2b_escape s) style_att_bs = Style_Att_30 instance A_Style Att28 where style_att s = Style_Att_28 (s2b_escape s) style_att_bs = Style_Att_28 instance A_Style Att27 where style_att s = Style_Att_27 (s2b_escape s) style_att_bs = Style_Att_27 instance A_Style Att25 where style_att s = Style_Att_25 (s2b_escape s) style_att_bs = Style_Att_25 instance A_Style Att22 where style_att s = Style_Att_22 (s2b_escape s) style_att_bs = Style_Att_22 instance A_Style Att20 where style_att s = Style_Att_20 (s2b_escape s) style_att_bs = Style_Att_20 instance A_Style Att19 where style_att s = Style_Att_19 (s2b_escape s) style_att_bs = Style_Att_19 instance A_Style Att17 where style_att s = Style_Att_17 (s2b_escape s) style_att_bs = Style_Att_17 instance A_Style Att16 where style_att s = Style_Att_16 (s2b_escape s) style_att_bs = Style_Att_16 instance A_Style Att15 where style_att s = Style_Att_15 (s2b_escape s) style_att_bs = Style_Att_15 instance A_Style Att14 where style_att s = Style_Att_14 (s2b_escape s) style_att_bs = Style_Att_14 instance A_Style Att13 where style_att s = Style_Att_13 (s2b_escape s) style_att_bs = Style_Att_13 instance A_Style Att12 where style_att s = Style_Att_12 (s2b_escape s) style_att_bs = Style_Att_12 instance A_Style Att11 where style_att s = Style_Att_11 (s2b_escape s) style_att_bs = Style_Att_11 instance A_Style Att7 where style_att s = Style_Att_7 (s2b_escape s) style_att_bs = Style_Att_7 class A_Onmousemove a where onmousemove_att :: String -> a onmousemove_att_bs :: B.ByteString -> a instance A_Onmousemove Att44 where onmousemove_att s = Onmousemove_Att_44 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_44 instance A_Onmousemove Att43 where onmousemove_att s = Onmousemove_Att_43 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_43 instance A_Onmousemove Att42 where onmousemove_att s = Onmousemove_Att_42 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_42 instance A_Onmousemove Att41 where onmousemove_att s = Onmousemove_Att_41 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_41 instance A_Onmousemove Att40 where onmousemove_att s = Onmousemove_Att_40 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_40 instance A_Onmousemove Att39 where onmousemove_att s = Onmousemove_Att_39 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_39 instance A_Onmousemove Att36 where onmousemove_att s = Onmousemove_Att_36 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_36 instance A_Onmousemove Att35 where onmousemove_att s = Onmousemove_Att_35 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_35 instance A_Onmousemove Att33 where onmousemove_att s = Onmousemove_Att_33 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_33 instance A_Onmousemove Att32 where onmousemove_att s = Onmousemove_Att_32 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_32 instance A_Onmousemove Att31 where onmousemove_att s = Onmousemove_Att_31 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_31 instance A_Onmousemove Att30 where onmousemove_att s = Onmousemove_Att_30 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_30 instance A_Onmousemove Att28 where onmousemove_att s = Onmousemove_Att_28 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_28 instance A_Onmousemove Att27 where onmousemove_att s = Onmousemove_Att_27 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_27 instance A_Onmousemove Att25 where onmousemove_att s = Onmousemove_Att_25 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_25 instance A_Onmousemove Att22 where onmousemove_att s = Onmousemove_Att_22 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_22 instance A_Onmousemove Att20 where onmousemove_att s = Onmousemove_Att_20 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_20 instance A_Onmousemove Att17 where onmousemove_att s = Onmousemove_Att_17 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_17 instance A_Onmousemove Att16 where onmousemove_att s = Onmousemove_Att_16 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_16 instance A_Onmousemove Att15 where onmousemove_att s = Onmousemove_Att_15 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_15 instance A_Onmousemove Att14 where onmousemove_att s = Onmousemove_Att_14 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_14 instance A_Onmousemove Att13 where onmousemove_att s = Onmousemove_Att_13 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_13 instance A_Onmousemove Att12 where onmousemove_att s = Onmousemove_Att_12 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_12 instance A_Onmousemove Att11 where onmousemove_att s = Onmousemove_Att_11 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_11 instance A_Onmousemove Att7 where onmousemove_att s = Onmousemove_Att_7 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_7 class A_Height a where height_att :: String -> a height_att_bs :: B.ByteString -> a instance A_Height Att22 where height_att s = Height_Att_22 (s2b_escape s) height_att_bs = Height_Att_22 instance A_Height Att20 where height_att s = Height_Att_20 (s2b_escape s) height_att_bs = Height_Att_20 class A_Codetype a where codetype_att :: String -> a codetype_att_bs :: B.ByteString -> a instance A_Codetype Att20 where codetype_att s = Codetype_Att_20 (s2b_escape s) codetype_att_bs = Codetype_Att_20 class A_Char a where char_att :: String -> a char_att_bs :: B.ByteString -> a instance A_Char Att44 where char_att s = Char_Att_44 (s2b_escape s) char_att_bs = Char_Att_44 instance A_Char Att43 where char_att s = Char_Att_43 (s2b_escape s) char_att_bs = Char_Att_43 instance A_Char Att42 where char_att s = Char_Att_42 (s2b_escape s) char_att_bs = Char_Att_42 class A_Multiple a where multiple_att :: String -> a instance A_Multiple Att32 where multiple_att s = Multiple_Att_32 (s2b (show s)) class A_Codebase a where codebase_att :: String -> a codebase_att_bs :: B.ByteString -> a instance A_Codebase Att20 where codebase_att s = Codebase_Att_20 (s2b_escape s) codebase_att_bs = Codebase_Att_20 class A_Xmlns a where xmlns_att :: String -> a xmlns_att_bs :: B.ByteString -> a instance A_Xmlns Att0 where xmlns_att s = Xmlns_Att_0 (s2b_escape s) xmlns_att_bs = Xmlns_Att_0 class A_Profile a where profile_att :: String -> a profile_att_bs :: B.ByteString -> a instance A_Profile Att1 where profile_att s = Profile_Att_1 (s2b_escape s) profile_att_bs = Profile_Att_1 class A_Rel a where rel_att :: String -> a rel_att_bs :: B.ByteString -> a instance A_Rel Att16 where rel_att s = Rel_Att_16 (s2b_escape s) rel_att_bs = Rel_Att_16 instance A_Rel Att7 where rel_att s = Rel_Att_7 (s2b_escape s) rel_att_bs = Rel_Att_7 class A_Onsubmit a where onsubmit_att :: String -> a onsubmit_att_bs :: B.ByteString -> a instance A_Onsubmit Att28 where onsubmit_att s = Onsubmit_Att_28 (s2b_escape s) onsubmit_att_bs = Onsubmit_Att_28 class A_Ondblclick a where ondblclick_att :: String -> a ondblclick_att_bs :: B.ByteString -> a instance A_Ondblclick Att44 where ondblclick_att s = Ondblclick_Att_44 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_44 instance A_Ondblclick Att43 where ondblclick_att s = Ondblclick_Att_43 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_43 instance A_Ondblclick Att42 where ondblclick_att s = Ondblclick_Att_42 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_42 instance A_Ondblclick Att41 where ondblclick_att s = Ondblclick_Att_41 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_41 instance A_Ondblclick Att40 where ondblclick_att s = Ondblclick_Att_40 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_40 instance A_Ondblclick Att39 where ondblclick_att s = Ondblclick_Att_39 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_39 instance A_Ondblclick Att36 where ondblclick_att s = Ondblclick_Att_36 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_36 instance A_Ondblclick Att35 where ondblclick_att s = Ondblclick_Att_35 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_35 instance A_Ondblclick Att33 where ondblclick_att s = Ondblclick_Att_33 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_33 instance A_Ondblclick Att32 where ondblclick_att s = Ondblclick_Att_32 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_32 instance A_Ondblclick Att31 where ondblclick_att s = Ondblclick_Att_31 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_31 instance A_Ondblclick Att30 where ondblclick_att s = Ondblclick_Att_30 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_30 instance A_Ondblclick Att28 where ondblclick_att s = Ondblclick_Att_28 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_28 instance A_Ondblclick Att27 where ondblclick_att s = Ondblclick_Att_27 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_27 instance A_Ondblclick Att25 where ondblclick_att s = Ondblclick_Att_25 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_25 instance A_Ondblclick Att22 where ondblclick_att s = Ondblclick_Att_22 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_22 instance A_Ondblclick Att20 where ondblclick_att s = Ondblclick_Att_20 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_20 instance A_Ondblclick Att17 where ondblclick_att s = Ondblclick_Att_17 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_17 instance A_Ondblclick Att16 where ondblclick_att s = Ondblclick_Att_16 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_16 instance A_Ondblclick Att15 where ondblclick_att s = Ondblclick_Att_15 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_15 instance A_Ondblclick Att14 where ondblclick_att s = Ondblclick_Att_14 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_14 instance A_Ondblclick Att13 where ondblclick_att s = Ondblclick_Att_13 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_13 instance A_Ondblclick Att12 where ondblclick_att s = Ondblclick_Att_12 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_12 instance A_Ondblclick Att11 where ondblclick_att s = Ondblclick_Att_11 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_11 instance A_Ondblclick Att7 where ondblclick_att s = Ondblclick_Att_7 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_7 class A_Axis a where axis_att :: String -> a axis_att_bs :: B.ByteString -> a instance A_Axis Att44 where axis_att s = Axis_Att_44 (s2b_escape s) axis_att_bs = Axis_Att_44 class A_Cols a where cols_att :: String -> a cols_att_bs :: B.ByteString -> a instance A_Cols Att38 where cols_att s = Cols_Att_38 (s2b_escape s) cols_att_bs = Cols_Att_38 instance A_Cols Att36 where cols_att s = Cols_Att_36 (s2b_escape s) cols_att_bs = Cols_Att_36 class A_Abbr a where abbr_att :: String -> a abbr_att_bs :: B.ByteString -> a instance A_Abbr Att44 where abbr_att s = Abbr_Att_44 (s2b_escape s) abbr_att_bs = Abbr_Att_44 class A_Onchange a where onchange_att :: String -> a onchange_att_bs :: B.ByteString -> a instance A_Onchange Att36 where onchange_att s = Onchange_Att_36 (s2b_escape s) onchange_att_bs = Onchange_Att_36 instance A_Onchange Att32 where onchange_att s = Onchange_Att_32 (s2b_escape s) onchange_att_bs = Onchange_Att_32 instance A_Onchange Att31 where onchange_att s = Onchange_Att_31 (s2b_escape s) onchange_att_bs = Onchange_Att_31 class A_Readonly a where readonly_att :: String -> a instance A_Readonly Att36 where readonly_att s = Readonly_Att_36 (s2b (show s)) instance A_Readonly Att31 where readonly_att s = Readonly_Att_31 (s2b (show s)) class A_Href a where href_att :: String -> a href_att_bs :: B.ByteString -> a instance A_Href Att27 where href_att s = Href_Att_27 (s2b_escape s) href_att_bs = Href_Att_27 instance A_Href Att16 where href_att s = Href_Att_16 (s2b_escape s) href_att_bs = Href_Att_16 instance A_Href Att7 where href_att s = Href_Att_7 (s2b_escape s) href_att_bs = Href_Att_7 instance A_Href Att4 where href_att s = Href_Att_4 (s2b_escape s) href_att_bs = Href_Att_4 instance A_Href Att3 where href_att s = Href_Att_3 (s2b_escape s) href_att_bs = Href_Att_3 class A_Media a where media_att :: String -> a media_att_bs :: B.ByteString -> a instance A_Media Att8 where media_att s = Media_Att_8 (s2b_escape s) media_att_bs = Media_Att_8 instance A_Media Att7 where media_att s = Media_Att_7 (s2b_escape s) media_att_bs = Media_Att_7 class A_Id a where id_att :: String -> a id_att_bs :: B.ByteString -> a instance A_Id Att44 where id_att s = Id_Att_44 (s2b_escape s) id_att_bs = Id_Att_44 instance A_Id Att43 where id_att s = Id_Att_43 (s2b_escape s) id_att_bs = Id_Att_43 instance A_Id Att42 where id_att s = Id_Att_42 (s2b_escape s) id_att_bs = Id_Att_42 instance A_Id Att41 where id_att s = Id_Att_41 (s2b_escape s) id_att_bs = Id_Att_41 instance A_Id Att40 where id_att s = Id_Att_40 (s2b_escape s) id_att_bs = Id_Att_40 instance A_Id Att39 where id_att s = Id_Att_39 (s2b_escape s) id_att_bs = Id_Att_39 instance A_Id Att36 where id_att s = Id_Att_36 (s2b_escape s) id_att_bs = Id_Att_36 instance A_Id Att35 where id_att s = Id_Att_35 (s2b_escape s) id_att_bs = Id_Att_35 instance A_Id Att33 where id_att s = Id_Att_33 (s2b_escape s) id_att_bs = Id_Att_33 instance A_Id Att32 where id_att s = Id_Att_32 (s2b_escape s) id_att_bs = Id_Att_32 instance A_Id Att31 where id_att s = Id_Att_31 (s2b_escape s) id_att_bs = Id_Att_31 instance A_Id Att30 where id_att s = Id_Att_30 (s2b_escape s) id_att_bs = Id_Att_30 instance A_Id Att28 where id_att s = Id_Att_28 (s2b_escape s) id_att_bs = Id_Att_28 instance A_Id Att27 where id_att s = Id_Att_27 (s2b_escape s) id_att_bs = Id_Att_27 instance A_Id Att26 where id_att s = Id_Att_26 (s2b_escape s) id_att_bs = Id_Att_26 instance A_Id Att25 where id_att s = Id_Att_25 (s2b_escape s) id_att_bs = Id_Att_25 instance A_Id Att22 where id_att s = Id_Att_22 (s2b_escape s) id_att_bs = Id_Att_22 instance A_Id Att21 where id_att s = Id_Att_21 (s2b_escape s) id_att_bs = Id_Att_21 instance A_Id Att20 where id_att s = Id_Att_20 (s2b_escape s) id_att_bs = Id_Att_20 instance A_Id Att19 where id_att s = Id_Att_19 (s2b_escape s) id_att_bs = Id_Att_19 instance A_Id Att17 where id_att s = Id_Att_17 (s2b_escape s) id_att_bs = Id_Att_17 instance A_Id Att16 where id_att s = Id_Att_16 (s2b_escape s) id_att_bs = Id_Att_16 instance A_Id Att15 where id_att s = Id_Att_15 (s2b_escape s) id_att_bs = Id_Att_15 instance A_Id Att14 where id_att s = Id_Att_14 (s2b_escape s) id_att_bs = Id_Att_14 instance A_Id Att13 where id_att s = Id_Att_13 (s2b_escape s) id_att_bs = Id_Att_13 instance A_Id Att12 where id_att s = Id_Att_12 (s2b_escape s) id_att_bs = Id_Att_12 instance A_Id Att11 where id_att s = Id_Att_11 (s2b_escape s) id_att_bs = Id_Att_11 instance A_Id Att10 where id_att s = Id_Att_10 (s2b_escape s) id_att_bs = Id_Att_10 instance A_Id Att8 where id_att s = Id_Att_8 (s2b_escape s) id_att_bs = Id_Att_8 instance A_Id Att7 where id_att s = Id_Att_7 (s2b_escape s) id_att_bs = Id_Att_7 instance A_Id Att5 where id_att s = Id_Att_5 (s2b_escape s) id_att_bs = Id_Att_5 instance A_Id Att3 where id_att s = Id_Att_3 (s2b_escape s) id_att_bs = Id_Att_3 instance A_Id Att2 where id_att s = Id_Att_2 (s2b_escape s) id_att_bs = Id_Att_2 instance A_Id Att1 where id_att s = Id_Att_1 (s2b_escape s) id_att_bs = Id_Att_1 instance A_Id Att0 where id_att s = Id_Att_0 (s2b_escape s) id_att_bs = Id_Att_0 class A_For a where for_att :: String -> a for_att_bs :: B.ByteString -> a instance A_For Att30 where for_att s = For_Att_30 (s2b_escape s) for_att_bs = For_Att_30 class A_Src a where src_att :: String -> a src_att_bs :: B.ByteString -> a instance A_Src Att31 where src_att s = Src_Att_31 (s2b_escape s) src_att_bs = Src_Att_31 instance A_Src Att23 where src_att s = Src_Att_23 (s2b_escape s) src_att_bs = Src_Att_23 instance A_Src Att22 where src_att s = Src_Att_22 (s2b_escape s) src_att_bs = Src_Att_22 instance A_Src Att10 where src_att s = Src_Att_10 (s2b_escape s) src_att_bs = Src_Att_10 class A_Value a where value_att :: String -> a value_att_bs :: B.ByteString -> a instance A_Value Att40 where value_att s = Value_Att_40 (s2b_escape s) value_att_bs = Value_Att_40 instance A_Value Att35 where value_att s = Value_Att_35 (s2b_escape s) value_att_bs = Value_Att_35 instance A_Value Att31 where value_att s = Value_Att_31 (s2b_escape s) value_att_bs = Value_Att_31 instance A_Value Att21 where value_att s = Value_Att_21 (s2b_escape s) value_att_bs = Value_Att_21 class A_Data a where data_att :: String -> a data_att_bs :: B.ByteString -> a instance A_Data Att20 where data_att s = Data_Att_20 (s2b_escape s) data_att_bs = Data_Att_20 class A_Hreflang a where hreflang_att :: String -> a hreflang_att_bs :: B.ByteString -> a instance A_Hreflang Att16 where hreflang_att s = Hreflang_Att_16 (s2b_escape s) hreflang_att_bs = Hreflang_Att_16 instance A_Hreflang Att7 where hreflang_att s = Hreflang_Att_7 (s2b_escape s) hreflang_att_bs = Hreflang_Att_7 class A_Checked a where checked_att :: String -> a instance A_Checked Att31 where checked_att s = Checked_Att_31 (s2b (show s)) class A_Declare a where declare_att :: String -> a instance A_Declare Att20 where declare_att s = Declare_Att_20 (s2b (show s)) class A_Onkeypress a where onkeypress_att :: String -> a onkeypress_att_bs :: B.ByteString -> a instance A_Onkeypress Att44 where onkeypress_att s = Onkeypress_Att_44 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_44 instance A_Onkeypress Att43 where onkeypress_att s = Onkeypress_Att_43 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_43 instance A_Onkeypress Att42 where onkeypress_att s = Onkeypress_Att_42 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_42 instance A_Onkeypress Att41 where onkeypress_att s = Onkeypress_Att_41 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_41 instance A_Onkeypress Att40 where onkeypress_att s = Onkeypress_Att_40 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_40 instance A_Onkeypress Att39 where onkeypress_att s = Onkeypress_Att_39 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_39 instance A_Onkeypress Att36 where onkeypress_att s = Onkeypress_Att_36 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_36 instance A_Onkeypress Att35 where onkeypress_att s = Onkeypress_Att_35 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_35 instance A_Onkeypress Att33 where onkeypress_att s = Onkeypress_Att_33 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_33 instance A_Onkeypress Att32 where onkeypress_att s = Onkeypress_Att_32 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_32 instance A_Onkeypress Att31 where onkeypress_att s = Onkeypress_Att_31 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_31 instance A_Onkeypress Att30 where onkeypress_att s = Onkeypress_Att_30 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_30 instance A_Onkeypress Att28 where onkeypress_att s = Onkeypress_Att_28 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_28 instance A_Onkeypress Att27 where onkeypress_att s = Onkeypress_Att_27 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_27 instance A_Onkeypress Att25 where onkeypress_att s = Onkeypress_Att_25 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_25 instance A_Onkeypress Att22 where onkeypress_att s = Onkeypress_Att_22 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_22 instance A_Onkeypress Att20 where onkeypress_att s = Onkeypress_Att_20 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_20 instance A_Onkeypress Att17 where onkeypress_att s = Onkeypress_Att_17 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_17 instance A_Onkeypress Att16 where onkeypress_att s = Onkeypress_Att_16 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_16 instance A_Onkeypress Att15 where onkeypress_att s = Onkeypress_Att_15 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_15 instance A_Onkeypress Att14 where onkeypress_att s = Onkeypress_Att_14 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_14 instance A_Onkeypress Att13 where onkeypress_att s = Onkeypress_Att_13 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_13 instance A_Onkeypress Att12 where onkeypress_att s = Onkeypress_Att_12 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_12 instance A_Onkeypress Att11 where onkeypress_att s = Onkeypress_Att_11 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_11 instance A_Onkeypress Att7 where onkeypress_att s = Onkeypress_Att_7 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_7 class A_Label a where label_att :: String -> a label_att_bs :: B.ByteString -> a instance A_Label Att35 where label_att s = Label_Att_35 (s2b_escape s) label_att_bs = Label_Att_35 instance A_Label Att34 where label_att s = Label_Att_34 (s2b_escape s) label_att_bs = Label_Att_34 instance A_Label Att33 where label_att s = Label_Att_33 (s2b_escape s) label_att_bs = Label_Att_33 class A_Class a where class_att :: String -> a class_att_bs :: B.ByteString -> a instance A_Class Att44 where class_att s = Class_Att_44 (s2b_escape s) class_att_bs = Class_Att_44 instance A_Class Att43 where class_att s = Class_Att_43 (s2b_escape s) class_att_bs = Class_Att_43 instance A_Class Att42 where class_att s = Class_Att_42 (s2b_escape s) class_att_bs = Class_Att_42 instance A_Class Att41 where class_att s = Class_Att_41 (s2b_escape s) class_att_bs = Class_Att_41 instance A_Class Att40 where class_att s = Class_Att_40 (s2b_escape s) class_att_bs = Class_Att_40 instance A_Class Att39 where class_att s = Class_Att_39 (s2b_escape s) class_att_bs = Class_Att_39 instance A_Class Att36 where class_att s = Class_Att_36 (s2b_escape s) class_att_bs = Class_Att_36 instance A_Class Att35 where class_att s = Class_Att_35 (s2b_escape s) class_att_bs = Class_Att_35 instance A_Class Att33 where class_att s = Class_Att_33 (s2b_escape s) class_att_bs = Class_Att_33 instance A_Class Att32 where class_att s = Class_Att_32 (s2b_escape s) class_att_bs = Class_Att_32 instance A_Class Att31 where class_att s = Class_Att_31 (s2b_escape s) class_att_bs = Class_Att_31 instance A_Class Att30 where class_att s = Class_Att_30 (s2b_escape s) class_att_bs = Class_Att_30 instance A_Class Att28 where class_att s = Class_Att_28 (s2b_escape s) class_att_bs = Class_Att_28 instance A_Class Att27 where class_att s = Class_Att_27 (s2b_escape s) class_att_bs = Class_Att_27 instance A_Class Att25 where class_att s = Class_Att_25 (s2b_escape s) class_att_bs = Class_Att_25 instance A_Class Att22 where class_att s = Class_Att_22 (s2b_escape s) class_att_bs = Class_Att_22 instance A_Class Att20 where class_att s = Class_Att_20 (s2b_escape s) class_att_bs = Class_Att_20 instance A_Class Att19 where class_att s = Class_Att_19 (s2b_escape s) class_att_bs = Class_Att_19 instance A_Class Att17 where class_att s = Class_Att_17 (s2b_escape s) class_att_bs = Class_Att_17 instance A_Class Att16 where class_att s = Class_Att_16 (s2b_escape s) class_att_bs = Class_Att_16 instance A_Class Att15 where class_att s = Class_Att_15 (s2b_escape s) class_att_bs = Class_Att_15 instance A_Class Att14 where class_att s = Class_Att_14 (s2b_escape s) class_att_bs = Class_Att_14 instance A_Class Att13 where class_att s = Class_Att_13 (s2b_escape s) class_att_bs = Class_Att_13 instance A_Class Att12 where class_att s = Class_Att_12 (s2b_escape s) class_att_bs = Class_Att_12 instance A_Class Att11 where class_att s = Class_Att_11 (s2b_escape s) class_att_bs = Class_Att_11 instance A_Class Att7 where class_att s = Class_Att_7 (s2b_escape s) class_att_bs = Class_Att_7 class A_Type a where type_att :: String -> a instance A_Type Att40 where type_att s = Type_Att_40 (s2b (show s)) instance A_Type Att31 where type_att s = Type_Att_31 (s2b (show s)) instance A_Type Att21 where type_att s = Type_Att_21 (s2b (show s)) instance A_Type Att20 where type_att s = Type_Att_20 (s2b (show s)) instance A_Type Att16 where type_att s = Type_Att_16 (s2b (show s)) instance A_Type Att10 where type_att s = Type_Att_10 (s2b (show s)) instance A_Type Att9 where type_att s = Type_Att_9 (s2b (show s)) instance A_Type Att8 where type_att s = Type_Att_8 (s2b (show s)) instance A_Type Att7 where type_att s = Type_Att_7 (s2b (show s)) class A_Shape a where shape_att :: ShapeEnum -> a instance A_Shape Att27 where shape_att s = Shape_Att_27 (s2b (show s)) instance A_Shape Att16 where shape_att s = Shape_Att_16 (s2b (show s)) class A_Accesskey a where accesskey_att :: String -> a accesskey_att_bs :: B.ByteString -> a instance A_Accesskey Att40 where accesskey_att s = Accesskey_Att_40 (s2b_escape s) accesskey_att_bs = Accesskey_Att_40 instance A_Accesskey Att39 where accesskey_att s = Accesskey_Att_39 (s2b_escape s) accesskey_att_bs = Accesskey_Att_39 instance A_Accesskey Att36 where accesskey_att s = Accesskey_Att_36 (s2b_escape s) accesskey_att_bs = Accesskey_Att_36 instance A_Accesskey Att31 where accesskey_att s = Accesskey_Att_31 (s2b_escape s) accesskey_att_bs = Accesskey_Att_31 instance A_Accesskey Att30 where accesskey_att s = Accesskey_Att_30 (s2b_escape s) accesskey_att_bs = Accesskey_Att_30 instance A_Accesskey Att27 where accesskey_att s = Accesskey_Att_27 (s2b_escape s) accesskey_att_bs = Accesskey_Att_27 instance A_Accesskey Att16 where accesskey_att s = Accesskey_Att_16 (s2b_escape s) accesskey_att_bs = Accesskey_Att_16 class A_Headers a where headers_att :: String -> a headers_att_bs :: B.ByteString -> a instance A_Headers Att44 where headers_att s = Headers_Att_44 (s2b_escape s) headers_att_bs = Headers_Att_44 class A_Disabled a where disabled_att :: String -> a instance A_Disabled Att40 where disabled_att s = Disabled_Att_40 (s2b (show s)) instance A_Disabled Att36 where disabled_att s = Disabled_Att_36 (s2b (show s)) instance A_Disabled Att35 where disabled_att s = Disabled_Att_35 (s2b (show s)) instance A_Disabled Att33 where disabled_att s = Disabled_Att_33 (s2b (show s)) instance A_Disabled Att32 where disabled_att s = Disabled_Att_32 (s2b (show s)) instance A_Disabled Att31 where disabled_att s = Disabled_Att_31 (s2b (show s)) class A_Rules a where rules_att :: RulesEnum -> a instance A_Rules Att41 where rules_att s = Rules_Att_41 (s2b (show s)) class A_Rows a where rows_att :: String -> a rows_att_bs :: B.ByteString -> a instance A_Rows Att37 where rows_att s = Rows_Att_37 (s2b_escape s) rows_att_bs = Rows_Att_37 instance A_Rows Att36 where rows_att s = Rows_Att_36 (s2b_escape s) rows_att_bs = Rows_Att_36 class A_Onfocus a where onfocus_att :: String -> a onfocus_att_bs :: B.ByteString -> a instance A_Onfocus Att40 where onfocus_att s = Onfocus_Att_40 (s2b_escape s) onfocus_att_bs = Onfocus_Att_40 instance A_Onfocus Att36 where onfocus_att s = Onfocus_Att_36 (s2b_escape s) onfocus_att_bs = Onfocus_Att_36 instance A_Onfocus Att32 where onfocus_att s = Onfocus_Att_32 (s2b_escape s) onfocus_att_bs = Onfocus_Att_32 instance A_Onfocus Att31 where onfocus_att s = Onfocus_Att_31 (s2b_escape s) onfocus_att_bs = Onfocus_Att_31 instance A_Onfocus Att30 where onfocus_att s = Onfocus_Att_30 (s2b_escape s) onfocus_att_bs = Onfocus_Att_30 instance A_Onfocus Att27 where onfocus_att s = Onfocus_Att_27 (s2b_escape s) onfocus_att_bs = Onfocus_Att_27 instance A_Onfocus Att16 where onfocus_att s = Onfocus_Att_16 (s2b_escape s) onfocus_att_bs = Onfocus_Att_16 class A_Colspan a where colspan_att :: String -> a colspan_att_bs :: B.ByteString -> a instance A_Colspan Att44 where colspan_att s = Colspan_Att_44 (s2b_escape s) colspan_att_bs = Colspan_Att_44 class A_Rowspan a where rowspan_att :: String -> a rowspan_att_bs :: B.ByteString -> a instance A_Rowspan Att44 where rowspan_att s = Rowspan_Att_44 (s2b_escape s) rowspan_att_bs = Rowspan_Att_44 class A_Defer a where defer_att :: String -> a instance A_Defer Att10 where defer_att s = Defer_Att_10 (s2b (show s)) class A_Cellspacing a where cellspacing_att :: String -> a cellspacing_att_bs :: B.ByteString -> a instance A_Cellspacing Att41 where cellspacing_att s = Cellspacing_Att_41 (s2b_escape s) cellspacing_att_bs = Cellspacing_Att_41 class A_Charoff a where charoff_att :: String -> a charoff_att_bs :: B.ByteString -> a instance A_Charoff Att44 where charoff_att s = Charoff_Att_44 (s2b_escape s) charoff_att_bs = Charoff_Att_44 instance A_Charoff Att43 where charoff_att s = Charoff_Att_43 (s2b_escape s) charoff_att_bs = Charoff_Att_43 instance A_Charoff Att42 where charoff_att s = Charoff_Att_42 (s2b_escape s) charoff_att_bs = Charoff_Att_42 class A_Cite a where cite_att :: String -> a cite_att_bs :: B.ByteString -> a instance A_Cite Att15 where cite_att s = Cite_Att_15 (s2b_escape s) cite_att_bs = Cite_Att_15 instance A_Cite Att14 where cite_att s = Cite_Att_14 (s2b_escape s) cite_att_bs = Cite_Att_14 class A_Maxlength a where maxlength_att :: String -> a maxlength_att_bs :: B.ByteString -> a instance A_Maxlength Att31 where maxlength_att s = Maxlength_Att_31 (s2b_escape s) maxlength_att_bs = Maxlength_Att_31 class A_Onselect a where onselect_att :: String -> a onselect_att_bs :: B.ByteString -> a instance A_Onselect Att36 where onselect_att s = Onselect_Att_36 (s2b_escape s) onselect_att_bs = Onselect_Att_36 instance A_Onselect Att31 where onselect_att s = Onselect_Att_31 (s2b_escape s) onselect_att_bs = Onselect_Att_31 class A_Accept a where accept_att :: String -> a accept_att_bs :: B.ByteString -> a instance A_Accept Att31 where accept_att s = Accept_Att_31 (s2b_escape s) accept_att_bs = Accept_Att_31 instance A_Accept Att28 where accept_att s = Accept_Att_28 (s2b_escape s) accept_att_bs = Accept_Att_28 class A_Archive a where archive_att :: String -> a archive_att_bs :: B.ByteString -> a instance A_Archive Att20 where archive_att s = Archive_Att_20 (s2b_escape s) archive_att_bs = Archive_Att_20 class A_Alt a where alt_att :: String -> a alt_att_bs :: B.ByteString -> a instance A_Alt Att31 where alt_att s = Alt_Att_31 (s2b_escape s) alt_att_bs = Alt_Att_31 instance A_Alt Att27 where alt_att s = Alt_Att_27 (s2b_escape s) alt_att_bs = Alt_Att_27 instance A_Alt Att24 where alt_att s = Alt_Att_24 (s2b_escape s) alt_att_bs = Alt_Att_24 instance A_Alt Att22 where alt_att s = Alt_Att_22 (s2b_escape s) alt_att_bs = Alt_Att_22 class A_Classid a where classid_att :: String -> a classid_att_bs :: B.ByteString -> a instance A_Classid Att20 where classid_att s = Classid_Att_20 (s2b_escape s) classid_att_bs = Classid_Att_20 class A_Longdesc a where longdesc_att :: String -> a longdesc_att_bs :: B.ByteString -> a instance A_Longdesc Att22 where longdesc_att s = Longdesc_Att_22 (s2b_escape s) longdesc_att_bs = Longdesc_Att_22 class A_Onmouseout a where onmouseout_att :: String -> a onmouseout_att_bs :: B.ByteString -> a instance A_Onmouseout Att44 where onmouseout_att s = Onmouseout_Att_44 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_44 instance A_Onmouseout Att43 where onmouseout_att s = Onmouseout_Att_43 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_43 instance A_Onmouseout Att42 where onmouseout_att s = Onmouseout_Att_42 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_42 instance A_Onmouseout Att41 where onmouseout_att s = Onmouseout_Att_41 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_41 instance A_Onmouseout Att40 where onmouseout_att s = Onmouseout_Att_40 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_40 instance A_Onmouseout Att39 where onmouseout_att s = Onmouseout_Att_39 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_39 instance A_Onmouseout Att36 where onmouseout_att s = Onmouseout_Att_36 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_36 instance A_Onmouseout Att35 where onmouseout_att s = Onmouseout_Att_35 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_35 instance A_Onmouseout Att33 where onmouseout_att s = Onmouseout_Att_33 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_33 instance A_Onmouseout Att32 where onmouseout_att s = Onmouseout_Att_32 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_32 instance A_Onmouseout Att31 where onmouseout_att s = Onmouseout_Att_31 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_31 instance A_Onmouseout Att30 where onmouseout_att s = Onmouseout_Att_30 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_30 instance A_Onmouseout Att28 where onmouseout_att s = Onmouseout_Att_28 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_28 instance A_Onmouseout Att27 where onmouseout_att s = Onmouseout_Att_27 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_27 instance A_Onmouseout Att25 where onmouseout_att s = Onmouseout_Att_25 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_25 instance A_Onmouseout Att22 where onmouseout_att s = Onmouseout_Att_22 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_22 instance A_Onmouseout Att20 where onmouseout_att s = Onmouseout_Att_20 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_20 instance A_Onmouseout Att17 where onmouseout_att s = Onmouseout_Att_17 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_17 instance A_Onmouseout Att16 where onmouseout_att s = Onmouseout_Att_16 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_16 instance A_Onmouseout Att15 where onmouseout_att s = Onmouseout_Att_15 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_15 instance A_Onmouseout Att14 where onmouseout_att s = Onmouseout_Att_14 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_14 instance A_Onmouseout Att13 where onmouseout_att s = Onmouseout_Att_13 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_13 instance A_Onmouseout Att12 where onmouseout_att s = Onmouseout_Att_12 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_12 instance A_Onmouseout Att11 where onmouseout_att s = Onmouseout_Att_11 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_11 instance A_Onmouseout Att7 where onmouseout_att s = Onmouseout_Att_7 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_7 class A_Space a where space_att :: String -> a instance A_Space Att13 where space_att s = Space_Att_13 (s2b (show s)) instance A_Space Att10 where space_att s = Space_Att_10 (s2b (show s)) instance A_Space Att8 where space_att s = Space_Att_8 (s2b (show s)) class A_Border a where border_att :: String -> a border_att_bs :: B.ByteString -> a instance A_Border Att41 where border_att s = Border_Att_41 (s2b_escape s) border_att_bs = Border_Att_41 class A_Onunload a where onunload_att :: String -> a onunload_att_bs :: B.ByteString -> a instance A_Onunload Att12 where onunload_att s = Onunload_Att_12 (s2b_escape s) onunload_att_bs = Onunload_Att_12 class A_Onload a where onload_att :: String -> a onload_att_bs :: B.ByteString -> a instance A_Onload Att12 where onload_att s = Onload_Att_12 (s2b_escape s) onload_att_bs = Onload_Att_12 class A_Action a where action_att :: String -> a action_att_bs :: B.ByteString -> a instance A_Action Att29 where action_att s = Action_Att_29 (s2b_escape s) action_att_bs = Action_Att_29 instance A_Action Att28 where action_att s = Action_Att_28 (s2b_escape s) action_att_bs = Action_Att_28 class A_Cellpadding a where cellpadding_att :: String -> a cellpadding_att_bs :: B.ByteString -> a instance A_Cellpadding Att41 where cellpadding_att s = Cellpadding_Att_41 (s2b_escape s) cellpadding_att_bs = Cellpadding_Att_41 class A_Valuetype a where valuetype_att :: ValuetypeEnum -> a instance A_Valuetype Att21 where valuetype_att s = Valuetype_Att_21 (s2b (show s)) class A_Selected a where selected_att :: String -> a instance A_Selected Att35 where selected_att s = Selected_Att_35 (s2b (show s)) class RenderAttribute a where renderAtt :: a -> (B.ByteString,B.ByteString) instance RenderAttribute Att44 where renderAtt (Id_Att_44 b) = (id_byte,b) renderAtt (Class_Att_44 b) = (class_byte,b) renderAtt (Style_Att_44 b) = (style_byte,b) renderAtt (Title_Att_44 b) = (title_byte,b) renderAtt (Lang_Att_44 b) = (lang_byte,b) renderAtt (Dir_Att_44 b) = (dir_byte,b) renderAtt (Onclick_Att_44 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_44 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_44 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_44 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_44 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_44 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_44 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_44 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_44 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_44 b) = (onkeyup_byte,b) renderAtt (Abbr_Att_44 b) = (abbr_byte,b) renderAtt (Axis_Att_44 b) = (axis_byte,b) renderAtt (Headers_Att_44 b) = (headers_byte,b) renderAtt (Scope_Att_44 b) = (scope_byte,b) renderAtt (Rowspan_Att_44 b) = (rowspan_byte,b) renderAtt (Colspan_Att_44 b) = (colspan_byte,b) renderAtt (Align_Att_44 b) = (align_byte,b) renderAtt (Char_Att_44 b) = (char_byte,b) renderAtt (Charoff_Att_44 b) = (charoff_byte,b) renderAtt (Valign_Att_44 b) = (valign_byte,b) instance RenderAttribute Att43 where renderAtt (Id_Att_43 b) = (id_byte,b) renderAtt (Class_Att_43 b) = (class_byte,b) renderAtt (Style_Att_43 b) = (style_byte,b) renderAtt (Title_Att_43 b) = (title_byte,b) renderAtt (Lang_Att_43 b) = (lang_byte,b) renderAtt (Dir_Att_43 b) = (dir_byte,b) renderAtt (Onclick_Att_43 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_43 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_43 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_43 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_43 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_43 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_43 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_43 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_43 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_43 b) = (onkeyup_byte,b) renderAtt (Span_Att_43 b) = (span_byte,b) renderAtt (Width_Att_43 b) = (width_byte,b) renderAtt (Align_Att_43 b) = (align_byte,b) renderAtt (Char_Att_43 b) = (char_byte,b) renderAtt (Charoff_Att_43 b) = (charoff_byte,b) renderAtt (Valign_Att_43 b) = (valign_byte,b) instance RenderAttribute Att42 where renderAtt (Id_Att_42 b) = (id_byte,b) renderAtt (Class_Att_42 b) = (class_byte,b) renderAtt (Style_Att_42 b) = (style_byte,b) renderAtt (Title_Att_42 b) = (title_byte,b) renderAtt (Lang_Att_42 b) = (lang_byte,b) renderAtt (Dir_Att_42 b) = (dir_byte,b) renderAtt (Onclick_Att_42 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_42 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_42 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_42 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_42 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_42 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_42 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_42 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_42 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_42 b) = (onkeyup_byte,b) renderAtt (Align_Att_42 b) = (align_byte,b) renderAtt (Char_Att_42 b) = (char_byte,b) renderAtt (Charoff_Att_42 b) = (charoff_byte,b) renderAtt (Valign_Att_42 b) = (valign_byte,b) instance RenderAttribute Att41 where renderAtt (Id_Att_41 b) = (id_byte,b) renderAtt (Class_Att_41 b) = (class_byte,b) renderAtt (Style_Att_41 b) = (style_byte,b) renderAtt (Title_Att_41 b) = (title_byte,b) renderAtt (Lang_Att_41 b) = (lang_byte,b) renderAtt (Dir_Att_41 b) = (dir_byte,b) renderAtt (Onclick_Att_41 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_41 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_41 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_41 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_41 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_41 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_41 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_41 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_41 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_41 b) = (onkeyup_byte,b) renderAtt (Summary_Att_41 b) = (summary_byte,b) renderAtt (Width_Att_41 b) = (width_byte,b) renderAtt (Border_Att_41 b) = (border_byte,b) renderAtt (Frame_Att_41 b) = (frame_byte,b) renderAtt (Rules_Att_41 b) = (rules_byte,b) renderAtt (Cellspacing_Att_41 b) = (cellspacing_byte,b) renderAtt (Cellpadding_Att_41 b) = (cellpadding_byte,b) instance RenderAttribute Att40 where renderAtt (Id_Att_40 b) = (id_byte,b) renderAtt (Class_Att_40 b) = (class_byte,b) renderAtt (Style_Att_40 b) = (style_byte,b) renderAtt (Title_Att_40 b) = (title_byte,b) renderAtt (Lang_Att_40 b) = (lang_byte,b) renderAtt (Dir_Att_40 b) = (dir_byte,b) renderAtt (Onclick_Att_40 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_40 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_40 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_40 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_40 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_40 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_40 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_40 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_40 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_40 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_40 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_40 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_40 b) = (onfocus_byte,b) renderAtt (Onblur_Att_40 b) = (onblur_byte,b) renderAtt (Name_Att_40 b) = (name_byte,b) renderAtt (Value_Att_40 b) = (value_byte,b) renderAtt (Type_Att_40 b) = (type_byte,b) renderAtt (Disabled_Att_40 b) = (disabled_byte,b) instance RenderAttribute Att39 where renderAtt (Id_Att_39 b) = (id_byte,b) renderAtt (Class_Att_39 b) = (class_byte,b) renderAtt (Style_Att_39 b) = (style_byte,b) renderAtt (Title_Att_39 b) = (title_byte,b) renderAtt (Lang_Att_39 b) = (lang_byte,b) renderAtt (Dir_Att_39 b) = (dir_byte,b) renderAtt (Onclick_Att_39 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_39 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_39 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_39 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_39 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_39 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_39 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_39 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_39 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_39 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_39 b) = (accesskey_byte,b) instance RenderAttribute Att38 where renderAtt (Cols_Att_38 b) = (cols_byte,b) instance RenderAttribute Att37 where renderAtt (Rows_Att_37 b) = (rows_byte,b) instance RenderAttribute Att36 where renderAtt (Id_Att_36 b) = (id_byte,b) renderAtt (Class_Att_36 b) = (class_byte,b) renderAtt (Style_Att_36 b) = (style_byte,b) renderAtt (Title_Att_36 b) = (title_byte,b) renderAtt (Lang_Att_36 b) = (lang_byte,b) renderAtt (Dir_Att_36 b) = (dir_byte,b) renderAtt (Onclick_Att_36 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_36 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_36 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_36 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_36 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_36 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_36 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_36 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_36 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_36 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_36 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_36 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_36 b) = (onfocus_byte,b) renderAtt (Onblur_Att_36 b) = (onblur_byte,b) renderAtt (Name_Att_36 b) = (name_byte,b) renderAtt (Rows_Att_36 b) = (rows_byte,b) renderAtt (Cols_Att_36 b) = (cols_byte,b) renderAtt (Disabled_Att_36 b) = (disabled_byte,b) renderAtt (Readonly_Att_36 b) = (readonly_byte,b) renderAtt (Onselect_Att_36 b) = (onselect_byte,b) renderAtt (Onchange_Att_36 b) = (onchange_byte,b) instance RenderAttribute Att35 where renderAtt (Id_Att_35 b) = (id_byte,b) renderAtt (Class_Att_35 b) = (class_byte,b) renderAtt (Style_Att_35 b) = (style_byte,b) renderAtt (Title_Att_35 b) = (title_byte,b) renderAtt (Lang_Att_35 b) = (lang_byte,b) renderAtt (Dir_Att_35 b) = (dir_byte,b) renderAtt (Onclick_Att_35 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_35 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_35 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_35 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_35 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_35 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_35 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_35 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_35 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_35 b) = (onkeyup_byte,b) renderAtt (Selected_Att_35 b) = (selected_byte,b) renderAtt (Disabled_Att_35 b) = (disabled_byte,b) renderAtt (Label_Att_35 b) = (label_byte,b) renderAtt (Value_Att_35 b) = (value_byte,b) instance RenderAttribute Att34 where renderAtt (Label_Att_34 b) = (label_byte,b) instance RenderAttribute Att33 where renderAtt (Id_Att_33 b) = (id_byte,b) renderAtt (Class_Att_33 b) = (class_byte,b) renderAtt (Style_Att_33 b) = (style_byte,b) renderAtt (Title_Att_33 b) = (title_byte,b) renderAtt (Lang_Att_33 b) = (lang_byte,b) renderAtt (Dir_Att_33 b) = (dir_byte,b) renderAtt (Onclick_Att_33 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_33 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_33 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_33 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_33 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_33 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_33 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_33 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_33 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_33 b) = (onkeyup_byte,b) renderAtt (Disabled_Att_33 b) = (disabled_byte,b) renderAtt (Label_Att_33 b) = (label_byte,b) instance RenderAttribute Att32 where renderAtt (Id_Att_32 b) = (id_byte,b) renderAtt (Class_Att_32 b) = (class_byte,b) renderAtt (Style_Att_32 b) = (style_byte,b) renderAtt (Title_Att_32 b) = (title_byte,b) renderAtt (Lang_Att_32 b) = (lang_byte,b) renderAtt (Dir_Att_32 b) = (dir_byte,b) renderAtt (Onclick_Att_32 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_32 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_32 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_32 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_32 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_32 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_32 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_32 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_32 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_32 b) = (onkeyup_byte,b) renderAtt (Name_Att_32 b) = (name_byte,b) renderAtt (Size_Att_32 b) = (size_byte,b) renderAtt (Multiple_Att_32 b) = (multiple_byte,b) renderAtt (Disabled_Att_32 b) = (disabled_byte,b) renderAtt (Tabindex_Att_32 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_32 b) = (onfocus_byte,b) renderAtt (Onblur_Att_32 b) = (onblur_byte,b) renderAtt (Onchange_Att_32 b) = (onchange_byte,b) instance RenderAttribute Att31 where renderAtt (Id_Att_31 b) = (id_byte,b) renderAtt (Class_Att_31 b) = (class_byte,b) renderAtt (Style_Att_31 b) = (style_byte,b) renderAtt (Title_Att_31 b) = (title_byte,b) renderAtt (Lang_Att_31 b) = (lang_byte,b) renderAtt (Dir_Att_31 b) = (dir_byte,b) renderAtt (Onclick_Att_31 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_31 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_31 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_31 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_31 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_31 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_31 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_31 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_31 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_31 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_31 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_31 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_31 b) = (onfocus_byte,b) renderAtt (Onblur_Att_31 b) = (onblur_byte,b) renderAtt (Type_Att_31 b) = (type_byte,b) renderAtt (Name_Att_31 b) = (name_byte,b) renderAtt (Value_Att_31 b) = (value_byte,b) renderAtt (Checked_Att_31 b) = (checked_byte,b) renderAtt (Disabled_Att_31 b) = (disabled_byte,b) renderAtt (Readonly_Att_31 b) = (readonly_byte,b) renderAtt (Size_Att_31 b) = (size_byte,b) renderAtt (Maxlength_Att_31 b) = (maxlength_byte,b) renderAtt (Src_Att_31 b) = (src_byte,b) renderAtt (Alt_Att_31 b) = (alt_byte,b) renderAtt (Usemap_Att_31 b) = (usemap_byte,b) renderAtt (Onselect_Att_31 b) = (onselect_byte,b) renderAtt (Onchange_Att_31 b) = (onchange_byte,b) renderAtt (Accept_Att_31 b) = (accept_byte,b) instance RenderAttribute Att30 where renderAtt (Id_Att_30 b) = (id_byte,b) renderAtt (Class_Att_30 b) = (class_byte,b) renderAtt (Style_Att_30 b) = (style_byte,b) renderAtt (Title_Att_30 b) = (title_byte,b) renderAtt (Lang_Att_30 b) = (lang_byte,b) renderAtt (Dir_Att_30 b) = (dir_byte,b) renderAtt (Onclick_Att_30 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_30 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_30 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_30 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_30 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_30 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_30 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_30 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_30 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_30 b) = (onkeyup_byte,b) renderAtt (For_Att_30 b) = (for_byte,b) renderAtt (Accesskey_Att_30 b) = (accesskey_byte,b) renderAtt (Onfocus_Att_30 b) = (onfocus_byte,b) renderAtt (Onblur_Att_30 b) = (onblur_byte,b) instance RenderAttribute Att29 where renderAtt (Action_Att_29 b) = (action_byte,b) instance RenderAttribute Att28 where renderAtt (Id_Att_28 b) = (id_byte,b) renderAtt (Class_Att_28 b) = (class_byte,b) renderAtt (Style_Att_28 b) = (style_byte,b) renderAtt (Title_Att_28 b) = (title_byte,b) renderAtt (Lang_Att_28 b) = (lang_byte,b) renderAtt (Dir_Att_28 b) = (dir_byte,b) renderAtt (Onclick_Att_28 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_28 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_28 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_28 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_28 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_28 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_28 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_28 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_28 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_28 b) = (onkeyup_byte,b) renderAtt (Action_Att_28 b) = (action_byte,b) renderAtt (Method_Att_28 b) = (method_byte,b) renderAtt (Enctype_Att_28 b) = (enctype_byte,b) renderAtt (Onsubmit_Att_28 b) = (onsubmit_byte,b) renderAtt (Onreset_Att_28 b) = (onreset_byte,b) renderAtt (Accept_Att_28 b) = (accept_byte,b) renderAtt (Accept_charset_Att_28 b) = (accept_charset_byte,b) instance RenderAttribute Att27 where renderAtt (Id_Att_27 b) = (id_byte,b) renderAtt (Class_Att_27 b) = (class_byte,b) renderAtt (Style_Att_27 b) = (style_byte,b) renderAtt (Title_Att_27 b) = (title_byte,b) renderAtt (Lang_Att_27 b) = (lang_byte,b) renderAtt (Dir_Att_27 b) = (dir_byte,b) renderAtt (Onclick_Att_27 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_27 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_27 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_27 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_27 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_27 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_27 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_27 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_27 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_27 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_27 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_27 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_27 b) = (onfocus_byte,b) renderAtt (Onblur_Att_27 b) = (onblur_byte,b) renderAtt (Shape_Att_27 b) = (shape_byte,b) renderAtt (Coords_Att_27 b) = (coords_byte,b) renderAtt (Href_Att_27 b) = (href_byte,b) renderAtt (Nohref_Att_27 b) = (nohref_byte,b) renderAtt (Alt_Att_27 b) = (alt_byte,b) instance RenderAttribute Att26 where renderAtt (Id_Att_26 b) = (id_byte,b) instance RenderAttribute Att25 where renderAtt (Lang_Att_25 b) = (lang_byte,b) renderAtt (Dir_Att_25 b) = (dir_byte,b) renderAtt (Onclick_Att_25 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_25 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_25 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_25 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_25 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_25 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_25 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_25 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_25 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_25 b) = (onkeyup_byte,b) renderAtt (Id_Att_25 b) = (id_byte,b) renderAtt (Class_Att_25 b) = (class_byte,b) renderAtt (Style_Att_25 b) = (style_byte,b) renderAtt (Title_Att_25 b) = (title_byte,b) renderAtt (Name_Att_25 b) = (name_byte,b) instance RenderAttribute Att24 where renderAtt (Alt_Att_24 b) = (alt_byte,b) instance RenderAttribute Att23 where renderAtt (Src_Att_23 b) = (src_byte,b) instance RenderAttribute Att22 where renderAtt (Id_Att_22 b) = (id_byte,b) renderAtt (Class_Att_22 b) = (class_byte,b) renderAtt (Style_Att_22 b) = (style_byte,b) renderAtt (Title_Att_22 b) = (title_byte,b) renderAtt (Lang_Att_22 b) = (lang_byte,b) renderAtt (Dir_Att_22 b) = (dir_byte,b) renderAtt (Onclick_Att_22 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_22 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_22 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_22 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_22 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_22 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_22 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_22 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_22 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_22 b) = (onkeyup_byte,b) renderAtt (Src_Att_22 b) = (src_byte,b) renderAtt (Alt_Att_22 b) = (alt_byte,b) renderAtt (Longdesc_Att_22 b) = (longdesc_byte,b) renderAtt (Height_Att_22 b) = (height_byte,b) renderAtt (Width_Att_22 b) = (width_byte,b) renderAtt (Usemap_Att_22 b) = (usemap_byte,b) renderAtt (Ismap_Att_22 b) = (ismap_byte,b) instance RenderAttribute Att21 where renderAtt (Id_Att_21 b) = (id_byte,b) renderAtt (Name_Att_21 b) = (name_byte,b) renderAtt (Value_Att_21 b) = (value_byte,b) renderAtt (Valuetype_Att_21 b) = (valuetype_byte,b) renderAtt (Type_Att_21 b) = (type_byte,b) instance RenderAttribute Att20 where renderAtt (Id_Att_20 b) = (id_byte,b) renderAtt (Class_Att_20 b) = (class_byte,b) renderAtt (Style_Att_20 b) = (style_byte,b) renderAtt (Title_Att_20 b) = (title_byte,b) renderAtt (Lang_Att_20 b) = (lang_byte,b) renderAtt (Dir_Att_20 b) = (dir_byte,b) renderAtt (Onclick_Att_20 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_20 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_20 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_20 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_20 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_20 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_20 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_20 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_20 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_20 b) = (onkeyup_byte,b) renderAtt (Declare_Att_20 b) = (declare_byte,b) renderAtt (Classid_Att_20 b) = (classid_byte,b) renderAtt (Codebase_Att_20 b) = (codebase_byte,b) renderAtt (Data_Att_20 b) = (data_byte,b) renderAtt (Type_Att_20 b) = (type_byte,b) renderAtt (Codetype_Att_20 b) = (codetype_byte,b) renderAtt (Archive_Att_20 b) = (archive_byte,b) renderAtt (Standby_Att_20 b) = (standby_byte,b) renderAtt (Height_Att_20 b) = (height_byte,b) renderAtt (Width_Att_20 b) = (width_byte,b) renderAtt (Usemap_Att_20 b) = (usemap_byte,b) renderAtt (Name_Att_20 b) = (name_byte,b) renderAtt (Tabindex_Att_20 b) = (tabindex_byte,b) instance RenderAttribute Att19 where renderAtt (Id_Att_19 b) = (id_byte,b) renderAtt (Class_Att_19 b) = (class_byte,b) renderAtt (Style_Att_19 b) = (style_byte,b) renderAtt (Title_Att_19 b) = (title_byte,b) instance RenderAttribute Att18 where renderAtt (Dir_Att_18 b) = (dir_byte,b) instance RenderAttribute Att17 where renderAtt (Id_Att_17 b) = (id_byte,b) renderAtt (Class_Att_17 b) = (class_byte,b) renderAtt (Style_Att_17 b) = (style_byte,b) renderAtt (Title_Att_17 b) = (title_byte,b) renderAtt (Onclick_Att_17 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_17 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_17 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_17 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_17 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_17 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_17 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_17 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_17 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_17 b) = (onkeyup_byte,b) renderAtt (Lang_Att_17 b) = (lang_byte,b) renderAtt (Dir_Att_17 b) = (dir_byte,b) instance RenderAttribute Att16 where renderAtt (Id_Att_16 b) = (id_byte,b) renderAtt (Class_Att_16 b) = (class_byte,b) renderAtt (Style_Att_16 b) = (style_byte,b) renderAtt (Title_Att_16 b) = (title_byte,b) renderAtt (Lang_Att_16 b) = (lang_byte,b) renderAtt (Dir_Att_16 b) = (dir_byte,b) renderAtt (Onclick_Att_16 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_16 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_16 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_16 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_16 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_16 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_16 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_16 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_16 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_16 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_16 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_16 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_16 b) = (onfocus_byte,b) renderAtt (Onblur_Att_16 b) = (onblur_byte,b) renderAtt (Charset_Att_16 b) = (charset_byte,b) renderAtt (Type_Att_16 b) = (type_byte,b) renderAtt (Name_Att_16 b) = (name_byte,b) renderAtt (Href_Att_16 b) = (href_byte,b) renderAtt (Hreflang_Att_16 b) = (hreflang_byte,b) renderAtt (Rel_Att_16 b) = (rel_byte,b) renderAtt (Rev_Att_16 b) = (rev_byte,b) renderAtt (Shape_Att_16 b) = (shape_byte,b) renderAtt (Coords_Att_16 b) = (coords_byte,b) instance RenderAttribute Att15 where renderAtt (Id_Att_15 b) = (id_byte,b) renderAtt (Class_Att_15 b) = (class_byte,b) renderAtt (Style_Att_15 b) = (style_byte,b) renderAtt (Title_Att_15 b) = (title_byte,b) renderAtt (Lang_Att_15 b) = (lang_byte,b) renderAtt (Dir_Att_15 b) = (dir_byte,b) renderAtt (Onclick_Att_15 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_15 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_15 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_15 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_15 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_15 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_15 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_15 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_15 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_15 b) = (onkeyup_byte,b) renderAtt (Cite_Att_15 b) = (cite_byte,b) renderAtt (Datetime_Att_15 b) = (datetime_byte,b) instance RenderAttribute Att14 where renderAtt (Id_Att_14 b) = (id_byte,b) renderAtt (Class_Att_14 b) = (class_byte,b) renderAtt (Style_Att_14 b) = (style_byte,b) renderAtt (Title_Att_14 b) = (title_byte,b) renderAtt (Lang_Att_14 b) = (lang_byte,b) renderAtt (Dir_Att_14 b) = (dir_byte,b) renderAtt (Onclick_Att_14 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_14 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_14 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_14 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_14 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_14 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_14 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_14 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_14 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_14 b) = (onkeyup_byte,b) renderAtt (Cite_Att_14 b) = (cite_byte,b) instance RenderAttribute Att13 where renderAtt (Id_Att_13 b) = (id_byte,b) renderAtt (Class_Att_13 b) = (class_byte,b) renderAtt (Style_Att_13 b) = (style_byte,b) renderAtt (Title_Att_13 b) = (title_byte,b) renderAtt (Lang_Att_13 b) = (lang_byte,b) renderAtt (Dir_Att_13 b) = (dir_byte,b) renderAtt (Onclick_Att_13 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_13 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_13 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_13 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_13 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_13 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_13 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_13 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_13 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_13 b) = (onkeyup_byte,b) renderAtt (Space_Att_13 b) = (space_byte,b) instance RenderAttribute Att12 where renderAtt (Id_Att_12 b) = (id_byte,b) renderAtt (Class_Att_12 b) = (class_byte,b) renderAtt (Style_Att_12 b) = (style_byte,b) renderAtt (Title_Att_12 b) = (title_byte,b) renderAtt (Lang_Att_12 b) = (lang_byte,b) renderAtt (Dir_Att_12 b) = (dir_byte,b) renderAtt (Onclick_Att_12 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_12 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_12 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_12 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_12 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_12 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_12 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_12 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_12 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_12 b) = (onkeyup_byte,b) renderAtt (Onload_Att_12 b) = (onload_byte,b) renderAtt (Onunload_Att_12 b) = (onunload_byte,b) instance RenderAttribute Att11 where renderAtt (Id_Att_11 b) = (id_byte,b) renderAtt (Class_Att_11 b) = (class_byte,b) renderAtt (Style_Att_11 b) = (style_byte,b) renderAtt (Title_Att_11 b) = (title_byte,b) renderAtt (Lang_Att_11 b) = (lang_byte,b) renderAtt (Dir_Att_11 b) = (dir_byte,b) renderAtt (Onclick_Att_11 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_11 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_11 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_11 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_11 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_11 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_11 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_11 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_11 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_11 b) = (onkeyup_byte,b) instance RenderAttribute Att10 where renderAtt (Id_Att_10 b) = (id_byte,b) renderAtt (Charset_Att_10 b) = (charset_byte,b) renderAtt (Type_Att_10 b) = (type_byte,b) renderAtt (Src_Att_10 b) = (src_byte,b) renderAtt (Defer_Att_10 b) = (defer_byte,b) renderAtt (Space_Att_10 b) = (space_byte,b) instance RenderAttribute Att9 where renderAtt (Type_Att_9 b) = (type_byte,b) instance RenderAttribute Att8 where renderAtt (Lang_Att_8 b) = (lang_byte,b) renderAtt (Dir_Att_8 b) = (dir_byte,b) renderAtt (Id_Att_8 b) = (id_byte,b) renderAtt (Type_Att_8 b) = (type_byte,b) renderAtt (Media_Att_8 b) = (media_byte,b) renderAtt (Title_Att_8 b) = (title_byte,b) renderAtt (Space_Att_8 b) = (space_byte,b) instance RenderAttribute Att7 where renderAtt (Id_Att_7 b) = (id_byte,b) renderAtt (Class_Att_7 b) = (class_byte,b) renderAtt (Style_Att_7 b) = (style_byte,b) renderAtt (Title_Att_7 b) = (title_byte,b) renderAtt (Lang_Att_7 b) = (lang_byte,b) renderAtt (Dir_Att_7 b) = (dir_byte,b) renderAtt (Onclick_Att_7 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_7 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_7 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_7 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_7 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_7 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_7 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_7 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_7 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_7 b) = (onkeyup_byte,b) renderAtt (Charset_Att_7 b) = (charset_byte,b) renderAtt (Href_Att_7 b) = (href_byte,b) renderAtt (Hreflang_Att_7 b) = (hreflang_byte,b) renderAtt (Type_Att_7 b) = (type_byte,b) renderAtt (Rel_Att_7 b) = (rel_byte,b) renderAtt (Rev_Att_7 b) = (rev_byte,b) renderAtt (Media_Att_7 b) = (media_byte,b) instance RenderAttribute Att6 where renderAtt (Content_Att_6 b) = (content_byte,b) instance RenderAttribute Att5 where renderAtt (Lang_Att_5 b) = (lang_byte,b) renderAtt (Dir_Att_5 b) = (dir_byte,b) renderAtt (Id_Att_5 b) = (id_byte,b) renderAtt (Http_equiv_Att_5 b) = (http_equiv_byte,b) renderAtt (Name_Att_5 b) = (name_byte,b) renderAtt (Content_Att_5 b) = (content_byte,b) renderAtt (Scheme_Att_5 b) = (scheme_byte,b) instance RenderAttribute Att4 where renderAtt (Href_Att_4 b) = (href_byte,b) instance RenderAttribute Att3 where renderAtt (Href_Att_3 b) = (href_byte,b) renderAtt (Id_Att_3 b) = (id_byte,b) instance RenderAttribute Att2 where renderAtt (Lang_Att_2 b) = (lang_byte,b) renderAtt (Dir_Att_2 b) = (dir_byte,b) renderAtt (Id_Att_2 b) = (id_byte,b) instance RenderAttribute Att1 where renderAtt (Lang_Att_1 b) = (lang_byte,b) renderAtt (Dir_Att_1 b) = (dir_byte,b) renderAtt (Id_Att_1 b) = (id_byte,b) renderAtt (Profile_Att_1 b) = (profile_byte,b) instance RenderAttribute Att0 where renderAtt (Lang_Att_0 b) = (lang_byte,b) renderAtt (Dir_Att_0 b) = (dir_byte,b) renderAtt (Id_Att_0 b) = (id_byte,b) renderAtt (Xmlns_Att_0 b) = (xmlns_byte,b) --renderAtts :: [Attributes] -> B.ByteString sp_byte = s2b " " eqq_byte = s2b "=\"" q_byte = s2b "\"" renderAtts [] = B.empty renderAtts (at:[]) = B.concat [sp_byte, a, eqq_byte, b, q_byte] where (a,b) = renderAtt at renderAtts at = B.concat (map (\(a,b)->B.concat [sp_byte, a, eqq_byte, b, q_byte]) (nubBy (\(a,b) (c,d)-> a==c) ats)) where ats = map renderAtt at data Ent0 = Head_0 [Att1] [Ent1] | Body_0 [Att12] [Ent27] deriving (Show) data Ent1 = Title_1 [Att2] [Ent2] | Base_1 [Att3] | Meta_1 [Att5] | Link_1 [Att7] | Style_1 [Att8] [Ent2] | Script_1 [Att10] [Ent2] | Object_1 [Att20] [Ent3] deriving (Show) data Ent2 = PCDATA_2 [Att0] B.ByteString deriving (Show) data Ent3 = Script_3 [Att10] [Ent2] | Noscript_3 [Att11] [Ent27] | Div_3 [Att11] [Ent28] | P_3 [Att11] [Ent22] | H1_3 [Att11] [Ent22] | H2_3 [Att11] [Ent22] | H3_3 [Att11] [Ent22] | H4_3 [Att11] [Ent22] | H5_3 [Att11] [Ent22] | H6_3 [Att11] [Ent22] | Ul_3 [Att11] [Ent29] | Ol_3 [Att11] [Ent29] | Dl_3 [Att11] [Ent30] | Address_3 [Att11] [Ent22] | Hr_3 [Att11] | Pre_3 [Att13] [Ent31] | Blockquote_3 [Att14] [Ent27] | Ins_3 [Att15] [Ent28] | Del_3 [Att15] [Ent28] | A_3 [Att16] [Ent4] | Span_3 [Att11] [Ent22] | Bdo_3 [Att11] [Ent22] | Br_3 [Att19] | Em_3 [Att11] [Ent22] | Strong_3 [Att11] [Ent22] | Dfn_3 [Att11] [Ent22] | Code_3 [Att11] [Ent22] | Samp_3 [Att11] [Ent22] | Kbd_3 [Att11] [Ent22] | Var_3 [Att11] [Ent22] | Cite_3 [Att11] [Ent22] | Abbr_3 [Att11] [Ent22] | Acronym_3 [Att11] [Ent22] | Q_3 [Att14] [Ent22] | Sub_3 [Att11] [Ent22] | Sup_3 [Att11] [Ent22] | Tt_3 [Att11] [Ent22] | I_3 [Att11] [Ent22] | B_3 [Att11] [Ent22] | Big_3 [Att11] [Ent22] | Small_3 [Att11] [Ent22] | Object_3 [Att20] [Ent3] | Param_3 [Att21] | Img_3 [Att22] | Map_3 [Att25] [Ent23] | Form_3 [Att28] [Ent32] | Label_3 [Att30] [Ent22] | Input_3 [Att31] | Select_3 [Att32] [Ent24] | Textarea_3 [Att36] [Ent2] | Fieldset_3 [Att11] [Ent33] | Button_3 [Att40] [Ent26] | Table_3 [Att41] [Ent34] | PCDATA_3 [Att0] B.ByteString deriving (Show) data Ent4 = Script_4 [Att10] [Ent5] | Ins_4 [Att15] [Ent6] | Del_4 [Att15] [Ent6] | Span_4 [Att11] [Ent4] | Bdo_4 [Att11] [Ent4] | Br_4 [Att19] | Em_4 [Att11] [Ent4] | Strong_4 [Att11] [Ent4] | Dfn_4 [Att11] [Ent4] | Code_4 [Att11] [Ent4] | Samp_4 [Att11] [Ent4] | Kbd_4 [Att11] [Ent4] | Var_4 [Att11] [Ent4] | Cite_4 [Att11] [Ent4] | Abbr_4 [Att11] [Ent4] | Acronym_4 [Att11] [Ent4] | Q_4 [Att14] [Ent4] | Sub_4 [Att11] [Ent4] | Sup_4 [Att11] [Ent4] | Tt_4 [Att11] [Ent4] | I_4 [Att11] [Ent4] | B_4 [Att11] [Ent4] | Big_4 [Att11] [Ent4] | Small_4 [Att11] [Ent4] | Object_4 [Att20] [Ent17] | Img_4 [Att22] | Map_4 [Att25] [Ent18] | Label_4 [Att30] [Ent4] | Input_4 [Att31] | Select_4 [Att32] [Ent19] | Textarea_4 [Att36] [Ent5] | Button_4 [Att40] [Ent21] | PCDATA_4 [Att0] B.ByteString deriving (Show) data Ent5 = PCDATA_5 [Att0] B.ByteString deriving (Show) data Ent6 = Script_6 [Att10] [Ent5] | Noscript_6 [Att11] [Ent7] | Div_6 [Att11] [Ent6] | P_6 [Att11] [Ent4] | H1_6 [Att11] [Ent4] | H2_6 [Att11] [Ent4] | H3_6 [Att11] [Ent4] | H4_6 [Att11] [Ent4] | H5_6 [Att11] [Ent4] | H6_6 [Att11] [Ent4] | Ul_6 [Att11] [Ent8] | Ol_6 [Att11] [Ent8] | Dl_6 [Att11] [Ent9] | Address_6 [Att11] [Ent4] | Hr_6 [Att11] | Pre_6 [Att13] [Ent10] | Blockquote_6 [Att14] [Ent7] | Ins_6 [Att15] [Ent6] | Del_6 [Att15] [Ent6] | Span_6 [Att11] [Ent4] | Bdo_6 [Att11] [Ent4] | Br_6 [Att19] | Em_6 [Att11] [Ent4] | Strong_6 [Att11] [Ent4] | Dfn_6 [Att11] [Ent4] | Code_6 [Att11] [Ent4] | Samp_6 [Att11] [Ent4] | Kbd_6 [Att11] [Ent4] | Var_6 [Att11] [Ent4] | Cite_6 [Att11] [Ent4] | Abbr_6 [Att11] [Ent4] | Acronym_6 [Att11] [Ent4] | Q_6 [Att14] [Ent4] | Sub_6 [Att11] [Ent4] | Sup_6 [Att11] [Ent4] | Tt_6 [Att11] [Ent4] | I_6 [Att11] [Ent4] | B_6 [Att11] [Ent4] | Big_6 [Att11] [Ent4] | Small_6 [Att11] [Ent4] | Object_6 [Att20] [Ent17] | Img_6 [Att22] | Map_6 [Att25] [Ent18] | Form_6 [Att28] [Ent11] | Label_6 [Att30] [Ent4] | Input_6 [Att31] | Select_6 [Att32] [Ent19] | Textarea_6 [Att36] [Ent5] | Fieldset_6 [Att11] [Ent12] | Button_6 [Att40] [Ent21] | Table_6 [Att41] [Ent13] | PCDATA_6 [Att0] B.ByteString deriving (Show) data Ent7 = Script_7 [Att10] [Ent5] | Noscript_7 [Att11] [Ent7] | Div_7 [Att11] [Ent6] | P_7 [Att11] [Ent4] | H1_7 [Att11] [Ent4] | H2_7 [Att11] [Ent4] | H3_7 [Att11] [Ent4] | H4_7 [Att11] [Ent4] | H5_7 [Att11] [Ent4] | H6_7 [Att11] [Ent4] | Ul_7 [Att11] [Ent8] | Ol_7 [Att11] [Ent8] | Dl_7 [Att11] [Ent9] | Address_7 [Att11] [Ent4] | Hr_7 [Att11] | Pre_7 [Att13] [Ent10] | Blockquote_7 [Att14] [Ent7] | Ins_7 [Att15] [Ent6] | Del_7 [Att15] [Ent6] | Form_7 [Att28] [Ent11] | Fieldset_7 [Att11] [Ent12] | Table_7 [Att41] [Ent13] deriving (Show) data Ent8 = Li_8 [Att11] [Ent6] deriving (Show) data Ent9 = Dt_9 [Att11] [Ent4] | Dd_9 [Att11] [Ent6] deriving (Show) data Ent10 = Script_10 [Att10] [Ent5] | Ins_10 [Att15] [Ent6] | Del_10 [Att15] [Ent6] | Span_10 [Att11] [Ent4] | Bdo_10 [Att11] [Ent4] | Br_10 [Att19] | Em_10 [Att11] [Ent4] | Strong_10 [Att11] [Ent4] | Dfn_10 [Att11] [Ent4] | Code_10 [Att11] [Ent4] | Samp_10 [Att11] [Ent4] | Kbd_10 [Att11] [Ent4] | Var_10 [Att11] [Ent4] | Cite_10 [Att11] [Ent4] | Abbr_10 [Att11] [Ent4] | Acronym_10 [Att11] [Ent4] | Q_10 [Att14] [Ent4] | Sub_10 [Att11] [Ent4] | Sup_10 [Att11] [Ent4] | Tt_10 [Att11] [Ent4] | I_10 [Att11] [Ent4] | B_10 [Att11] [Ent4] | Big_10 [Att11] [Ent4] | Small_10 [Att11] [Ent4] | Map_10 [Att25] [Ent18] | Label_10 [Att30] [Ent4] | Input_10 [Att31] | Select_10 [Att32] [Ent19] | Textarea_10 [Att36] [Ent5] | Button_10 [Att40] [Ent21] | PCDATA_10 [Att0] B.ByteString deriving (Show) data Ent11 = Script_11 [Att10] [Ent5] | Noscript_11 [Att11] [Ent7] | Div_11 [Att11] [Ent6] | P_11 [Att11] [Ent4] | H1_11 [Att11] [Ent4] | H2_11 [Att11] [Ent4] | H3_11 [Att11] [Ent4] | H4_11 [Att11] [Ent4] | H5_11 [Att11] [Ent4] | H6_11 [Att11] [Ent4] | Ul_11 [Att11] [Ent8] | Ol_11 [Att11] [Ent8] | Dl_11 [Att11] [Ent9] | Address_11 [Att11] [Ent4] | Hr_11 [Att11] | Pre_11 [Att13] [Ent10] | Blockquote_11 [Att14] [Ent7] | Ins_11 [Att15] [Ent6] | Del_11 [Att15] [Ent6] | Fieldset_11 [Att11] [Ent12] | Table_11 [Att41] [Ent13] deriving (Show) data Ent12 = Script_12 [Att10] [Ent5] | Noscript_12 [Att11] [Ent7] | Div_12 [Att11] [Ent6] | P_12 [Att11] [Ent4] | H1_12 [Att11] [Ent4] | H2_12 [Att11] [Ent4] | H3_12 [Att11] [Ent4] | H4_12 [Att11] [Ent4] | H5_12 [Att11] [Ent4] | H6_12 [Att11] [Ent4] | Ul_12 [Att11] [Ent8] | Ol_12 [Att11] [Ent8] | Dl_12 [Att11] [Ent9] | Address_12 [Att11] [Ent4] | Hr_12 [Att11] | Pre_12 [Att13] [Ent10] | Blockquote_12 [Att14] [Ent7] | Ins_12 [Att15] [Ent6] | Del_12 [Att15] [Ent6] | Span_12 [Att11] [Ent4] | Bdo_12 [Att11] [Ent4] | Br_12 [Att19] | Em_12 [Att11] [Ent4] | Strong_12 [Att11] [Ent4] | Dfn_12 [Att11] [Ent4] | Code_12 [Att11] [Ent4] | Samp_12 [Att11] [Ent4] | Kbd_12 [Att11] [Ent4] | Var_12 [Att11] [Ent4] | Cite_12 [Att11] [Ent4] | Abbr_12 [Att11] [Ent4] | Acronym_12 [Att11] [Ent4] | Q_12 [Att14] [Ent4] | Sub_12 [Att11] [Ent4] | Sup_12 [Att11] [Ent4] | Tt_12 [Att11] [Ent4] | I_12 [Att11] [Ent4] | B_12 [Att11] [Ent4] | Big_12 [Att11] [Ent4] | Small_12 [Att11] [Ent4] | Object_12 [Att20] [Ent17] | Img_12 [Att22] | Map_12 [Att25] [Ent18] | Form_12 [Att28] [Ent11] | Label_12 [Att30] [Ent4] | Input_12 [Att31] | Select_12 [Att32] [Ent19] | Textarea_12 [Att36] [Ent5] | Fieldset_12 [Att11] [Ent12] | Legend_12 [Att39] [Ent4] | Button_12 [Att40] [Ent21] | Table_12 [Att41] [Ent13] | PCDATA_12 [Att0] B.ByteString deriving (Show) data Ent13 = Caption_13 [Att11] [Ent4] | Thead_13 [Att42] [Ent14] | Tfoot_13 [Att42] [Ent14] | Tbody_13 [Att42] [Ent14] | Colgroup_13 [Att43] [Ent14] | Col_13 [Att43] | Tr_13 [Att42] [Ent16] deriving (Show) data Ent14 = Tr_14 [Att42] [Ent16] deriving (Show) data Ent15 = Col_15 [Att43] deriving (Show) data Ent16 = Th_16 [Att44] [Ent6] | Td_16 [Att44] [Ent6] deriving (Show) data Ent17 = Script_17 [Att10] [Ent5] | Noscript_17 [Att11] [Ent7] | Div_17 [Att11] [Ent6] | P_17 [Att11] [Ent4] | H1_17 [Att11] [Ent4] | H2_17 [Att11] [Ent4] | H3_17 [Att11] [Ent4] | H4_17 [Att11] [Ent4] | H5_17 [Att11] [Ent4] | H6_17 [Att11] [Ent4] | Ul_17 [Att11] [Ent8] | Ol_17 [Att11] [Ent8] | Dl_17 [Att11] [Ent9] | Address_17 [Att11] [Ent4] | Hr_17 [Att11] | Pre_17 [Att13] [Ent10] | Blockquote_17 [Att14] [Ent7] | Ins_17 [Att15] [Ent6] | Del_17 [Att15] [Ent6] | Span_17 [Att11] [Ent4] | Bdo_17 [Att11] [Ent4] | Br_17 [Att19] | Em_17 [Att11] [Ent4] | Strong_17 [Att11] [Ent4] | Dfn_17 [Att11] [Ent4] | Code_17 [Att11] [Ent4] | Samp_17 [Att11] [Ent4] | Kbd_17 [Att11] [Ent4] | Var_17 [Att11] [Ent4] | Cite_17 [Att11] [Ent4] | Abbr_17 [Att11] [Ent4] | Acronym_17 [Att11] [Ent4] | Q_17 [Att14] [Ent4] | Sub_17 [Att11] [Ent4] | Sup_17 [Att11] [Ent4] | Tt_17 [Att11] [Ent4] | I_17 [Att11] [Ent4] | B_17 [Att11] [Ent4] | Big_17 [Att11] [Ent4] | Small_17 [Att11] [Ent4] | Object_17 [Att20] [Ent17] | Param_17 [Att21] | Img_17 [Att22] | Map_17 [Att25] [Ent18] | Form_17 [Att28] [Ent11] | Label_17 [Att30] [Ent4] | Input_17 [Att31] | Select_17 [Att32] [Ent19] | Textarea_17 [Att36] [Ent5] | Fieldset_17 [Att11] [Ent12] | Button_17 [Att40] [Ent21] | Table_17 [Att41] [Ent13] | PCDATA_17 [Att0] B.ByteString deriving (Show) data Ent18 = Script_18 [Att10] [Ent5] | Noscript_18 [Att11] [Ent7] | Div_18 [Att11] [Ent6] | P_18 [Att11] [Ent4] | H1_18 [Att11] [Ent4] | H2_18 [Att11] [Ent4] | H3_18 [Att11] [Ent4] | H4_18 [Att11] [Ent4] | H5_18 [Att11] [Ent4] | H6_18 [Att11] [Ent4] | Ul_18 [Att11] [Ent8] | Ol_18 [Att11] [Ent8] | Dl_18 [Att11] [Ent9] | Address_18 [Att11] [Ent4] | Hr_18 [Att11] | Pre_18 [Att13] [Ent10] | Blockquote_18 [Att14] [Ent7] | Ins_18 [Att15] [Ent6] | Del_18 [Att15] [Ent6] | Area_18 [Att27] | Form_18 [Att28] [Ent11] | Fieldset_18 [Att11] [Ent12] | Table_18 [Att41] [Ent13] deriving (Show) data Ent19 = Optgroup_19 [Att33] [Ent20] | Option_19 [Att35] [Ent5] deriving (Show) data Ent20 = Option_20 [Att35] [Ent5] deriving (Show) data Ent21 = Script_21 [Att10] [Ent5] | Noscript_21 [Att11] [Ent7] | Div_21 [Att11] [Ent6] | P_21 [Att11] [Ent4] | H1_21 [Att11] [Ent4] | H2_21 [Att11] [Ent4] | H3_21 [Att11] [Ent4] | H4_21 [Att11] [Ent4] | H5_21 [Att11] [Ent4] | H6_21 [Att11] [Ent4] | Ul_21 [Att11] [Ent8] | Ol_21 [Att11] [Ent8] | Dl_21 [Att11] [Ent9] | Address_21 [Att11] [Ent4] | Hr_21 [Att11] | Pre_21 [Att13] [Ent10] | Blockquote_21 [Att14] [Ent7] | Ins_21 [Att15] [Ent6] | Del_21 [Att15] [Ent6] | Span_21 [Att11] [Ent4] | Bdo_21 [Att11] [Ent4] | Br_21 [Att19] | Em_21 [Att11] [Ent4] | Strong_21 [Att11] [Ent4] | Dfn_21 [Att11] [Ent4] | Code_21 [Att11] [Ent4] | Samp_21 [Att11] [Ent4] | Kbd_21 [Att11] [Ent4] | Var_21 [Att11] [Ent4] | Cite_21 [Att11] [Ent4] | Abbr_21 [Att11] [Ent4] | Acronym_21 [Att11] [Ent4] | Q_21 [Att14] [Ent4] | Sub_21 [Att11] [Ent4] | Sup_21 [Att11] [Ent4] | Tt_21 [Att11] [Ent4] | I_21 [Att11] [Ent4] | B_21 [Att11] [Ent4] | Big_21 [Att11] [Ent4] | Small_21 [Att11] [Ent4] | Object_21 [Att20] [Ent17] | Img_21 [Att22] | Map_21 [Att25] [Ent18] | Table_21 [Att41] [Ent13] | PCDATA_21 [Att0] B.ByteString deriving (Show) data Ent22 = Script_22 [Att10] [Ent2] | Ins_22 [Att15] [Ent28] | Del_22 [Att15] [Ent28] | A_22 [Att16] [Ent4] | Span_22 [Att11] [Ent22] | Bdo_22 [Att11] [Ent22] | Br_22 [Att19] | Em_22 [Att11] [Ent22] | Strong_22 [Att11] [Ent22] | Dfn_22 [Att11] [Ent22] | Code_22 [Att11] [Ent22] | Samp_22 [Att11] [Ent22] | Kbd_22 [Att11] [Ent22] | Var_22 [Att11] [Ent22] | Cite_22 [Att11] [Ent22] | Abbr_22 [Att11] [Ent22] | Acronym_22 [Att11] [Ent22] | Q_22 [Att14] [Ent22] | Sub_22 [Att11] [Ent22] | Sup_22 [Att11] [Ent22] | Tt_22 [Att11] [Ent22] | I_22 [Att11] [Ent22] | B_22 [Att11] [Ent22] | Big_22 [Att11] [Ent22] | Small_22 [Att11] [Ent22] | Object_22 [Att20] [Ent3] | Img_22 [Att22] | Map_22 [Att25] [Ent23] | Label_22 [Att30] [Ent22] | Input_22 [Att31] | Select_22 [Att32] [Ent24] | Textarea_22 [Att36] [Ent2] | Button_22 [Att40] [Ent26] | PCDATA_22 [Att0] B.ByteString deriving (Show) data Ent23 = Script_23 [Att10] [Ent2] | Noscript_23 [Att11] [Ent27] | Div_23 [Att11] [Ent28] | P_23 [Att11] [Ent22] | H1_23 [Att11] [Ent22] | H2_23 [Att11] [Ent22] | H3_23 [Att11] [Ent22] | H4_23 [Att11] [Ent22] | H5_23 [Att11] [Ent22] | H6_23 [Att11] [Ent22] | Ul_23 [Att11] [Ent29] | Ol_23 [Att11] [Ent29] | Dl_23 [Att11] [Ent30] | Address_23 [Att11] [Ent22] | Hr_23 [Att11] | Pre_23 [Att13] [Ent31] | Blockquote_23 [Att14] [Ent27] | Ins_23 [Att15] [Ent28] | Del_23 [Att15] [Ent28] | Area_23 [Att27] | Form_23 [Att28] [Ent32] | Fieldset_23 [Att11] [Ent33] | Table_23 [Att41] [Ent34] deriving (Show) data Ent24 = Optgroup_24 [Att33] [Ent25] | Option_24 [Att35] [Ent2] deriving (Show) data Ent25 = Option_25 [Att35] [Ent2] deriving (Show) data Ent26 = Script_26 [Att10] [Ent2] | Noscript_26 [Att11] [Ent27] | Div_26 [Att11] [Ent28] | P_26 [Att11] [Ent22] | H1_26 [Att11] [Ent22] | H2_26 [Att11] [Ent22] | H3_26 [Att11] [Ent22] | H4_26 [Att11] [Ent22] | H5_26 [Att11] [Ent22] | H6_26 [Att11] [Ent22] | Ul_26 [Att11] [Ent29] | Ol_26 [Att11] [Ent29] | Dl_26 [Att11] [Ent30] | Address_26 [Att11] [Ent22] | Hr_26 [Att11] | Pre_26 [Att13] [Ent31] | Blockquote_26 [Att14] [Ent27] | Ins_26 [Att15] [Ent28] | Del_26 [Att15] [Ent28] | Span_26 [Att11] [Ent22] | Bdo_26 [Att11] [Ent22] | Br_26 [Att19] | Em_26 [Att11] [Ent22] | Strong_26 [Att11] [Ent22] | Dfn_26 [Att11] [Ent22] | Code_26 [Att11] [Ent22] | Samp_26 [Att11] [Ent22] | Kbd_26 [Att11] [Ent22] | Var_26 [Att11] [Ent22] | Cite_26 [Att11] [Ent22] | Abbr_26 [Att11] [Ent22] | Acronym_26 [Att11] [Ent22] | Q_26 [Att14] [Ent22] | Sub_26 [Att11] [Ent22] | Sup_26 [Att11] [Ent22] | Tt_26 [Att11] [Ent22] | I_26 [Att11] [Ent22] | B_26 [Att11] [Ent22] | Big_26 [Att11] [Ent22] | Small_26 [Att11] [Ent22] | Object_26 [Att20] [Ent3] | Img_26 [Att22] | Map_26 [Att25] [Ent23] | Table_26 [Att41] [Ent34] | PCDATA_26 [Att0] B.ByteString deriving (Show) data Ent27 = Script_27 [Att10] [Ent2] | Noscript_27 [Att11] [Ent27] | Div_27 [Att11] [Ent28] | P_27 [Att11] [Ent22] | H1_27 [Att11] [Ent22] | H2_27 [Att11] [Ent22] | H3_27 [Att11] [Ent22] | H4_27 [Att11] [Ent22] | H5_27 [Att11] [Ent22] | H6_27 [Att11] [Ent22] | Ul_27 [Att11] [Ent29] | Ol_27 [Att11] [Ent29] | Dl_27 [Att11] [Ent30] | Address_27 [Att11] [Ent22] | Hr_27 [Att11] | Pre_27 [Att13] [Ent31] | Blockquote_27 [Att14] [Ent27] | Ins_27 [Att15] [Ent28] | Del_27 [Att15] [Ent28] | Form_27 [Att28] [Ent32] | Fieldset_27 [Att11] [Ent33] | Table_27 [Att41] [Ent34] deriving (Show) data Ent28 = Script_28 [Att10] [Ent2] | Noscript_28 [Att11] [Ent27] | Div_28 [Att11] [Ent28] | P_28 [Att11] [Ent22] | H1_28 [Att11] [Ent22] | H2_28 [Att11] [Ent22] | H3_28 [Att11] [Ent22] | H4_28 [Att11] [Ent22] | H5_28 [Att11] [Ent22] | H6_28 [Att11] [Ent22] | Ul_28 [Att11] [Ent29] | Ol_28 [Att11] [Ent29] | Dl_28 [Att11] [Ent30] | Address_28 [Att11] [Ent22] | Hr_28 [Att11] | Pre_28 [Att13] [Ent31] | Blockquote_28 [Att14] [Ent27] | Ins_28 [Att15] [Ent28] | Del_28 [Att15] [Ent28] | A_28 [Att16] [Ent4] | Span_28 [Att11] [Ent22] | Bdo_28 [Att11] [Ent22] | Br_28 [Att19] | Em_28 [Att11] [Ent22] | Strong_28 [Att11] [Ent22] | Dfn_28 [Att11] [Ent22] | Code_28 [Att11] [Ent22] | Samp_28 [Att11] [Ent22] | Kbd_28 [Att11] [Ent22] | Var_28 [Att11] [Ent22] | Cite_28 [Att11] [Ent22] | Abbr_28 [Att11] [Ent22] | Acronym_28 [Att11] [Ent22] | Q_28 [Att14] [Ent22] | Sub_28 [Att11] [Ent22] | Sup_28 [Att11] [Ent22] | Tt_28 [Att11] [Ent22] | I_28 [Att11] [Ent22] | B_28 [Att11] [Ent22] | Big_28 [Att11] [Ent22] | Small_28 [Att11] [Ent22] | Object_28 [Att20] [Ent3] | Img_28 [Att22] | Map_28 [Att25] [Ent23] | Form_28 [Att28] [Ent32] | Label_28 [Att30] [Ent22] | Input_28 [Att31] | Select_28 [Att32] [Ent24] | Textarea_28 [Att36] [Ent2] | Fieldset_28 [Att11] [Ent33] | Button_28 [Att40] [Ent26] | Table_28 [Att41] [Ent34] | PCDATA_28 [Att0] B.ByteString deriving (Show) data Ent29 = Li_29 [Att11] [Ent28] deriving (Show) data Ent30 = Dt_30 [Att11] [Ent22] | Dd_30 [Att11] [Ent28] deriving (Show) data Ent31 = Script_31 [Att10] [Ent2] | Ins_31 [Att15] [Ent28] | Del_31 [Att15] [Ent28] | A_31 [Att16] [Ent4] | Span_31 [Att11] [Ent22] | Bdo_31 [Att11] [Ent22] | Br_31 [Att19] | Em_31 [Att11] [Ent22] | Strong_31 [Att11] [Ent22] | Dfn_31 [Att11] [Ent22] | Code_31 [Att11] [Ent22] | Samp_31 [Att11] [Ent22] | Kbd_31 [Att11] [Ent22] | Var_31 [Att11] [Ent22] | Cite_31 [Att11] [Ent22] | Abbr_31 [Att11] [Ent22] | Acronym_31 [Att11] [Ent22] | Q_31 [Att14] [Ent22] | Sub_31 [Att11] [Ent22] | Sup_31 [Att11] [Ent22] | Tt_31 [Att11] [Ent22] | I_31 [Att11] [Ent22] | B_31 [Att11] [Ent22] | Big_31 [Att11] [Ent22] | Small_31 [Att11] [Ent22] | Map_31 [Att25] [Ent23] | Label_31 [Att30] [Ent22] | Input_31 [Att31] | Select_31 [Att32] [Ent24] | Textarea_31 [Att36] [Ent2] | Button_31 [Att40] [Ent26] | PCDATA_31 [Att0] B.ByteString deriving (Show) data Ent32 = Script_32 [Att10] [Ent2] | Noscript_32 [Att11] [Ent27] | Div_32 [Att11] [Ent28] | P_32 [Att11] [Ent22] | H1_32 [Att11] [Ent22] | H2_32 [Att11] [Ent22] | H3_32 [Att11] [Ent22] | H4_32 [Att11] [Ent22] | H5_32 [Att11] [Ent22] | H6_32 [Att11] [Ent22] | Ul_32 [Att11] [Ent29] | Ol_32 [Att11] [Ent29] | Dl_32 [Att11] [Ent30] | Address_32 [Att11] [Ent22] | Hr_32 [Att11] | Pre_32 [Att13] [Ent31] | Blockquote_32 [Att14] [Ent27] | Ins_32 [Att15] [Ent28] | Del_32 [Att15] [Ent28] | Fieldset_32 [Att11] [Ent33] | Table_32 [Att41] [Ent34] deriving (Show) data Ent33 = Script_33 [Att10] [Ent2] | Noscript_33 [Att11] [Ent27] | Div_33 [Att11] [Ent28] | P_33 [Att11] [Ent22] | H1_33 [Att11] [Ent22] | H2_33 [Att11] [Ent22] | H3_33 [Att11] [Ent22] | H4_33 [Att11] [Ent22] | H5_33 [Att11] [Ent22] | H6_33 [Att11] [Ent22] | Ul_33 [Att11] [Ent29] | Ol_33 [Att11] [Ent29] | Dl_33 [Att11] [Ent30] | Address_33 [Att11] [Ent22] | Hr_33 [Att11] | Pre_33 [Att13] [Ent31] | Blockquote_33 [Att14] [Ent27] | Ins_33 [Att15] [Ent28] | Del_33 [Att15] [Ent28] | A_33 [Att16] [Ent4] | Span_33 [Att11] [Ent22] | Bdo_33 [Att11] [Ent22] | Br_33 [Att19] | Em_33 [Att11] [Ent22] | Strong_33 [Att11] [Ent22] | Dfn_33 [Att11] [Ent22] | Code_33 [Att11] [Ent22] | Samp_33 [Att11] [Ent22] | Kbd_33 [Att11] [Ent22] | Var_33 [Att11] [Ent22] | Cite_33 [Att11] [Ent22] | Abbr_33 [Att11] [Ent22] | Acronym_33 [Att11] [Ent22] | Q_33 [Att14] [Ent22] | Sub_33 [Att11] [Ent22] | Sup_33 [Att11] [Ent22] | Tt_33 [Att11] [Ent22] | I_33 [Att11] [Ent22] | B_33 [Att11] [Ent22] | Big_33 [Att11] [Ent22] | Small_33 [Att11] [Ent22] | Object_33 [Att20] [Ent3] | Img_33 [Att22] | Map_33 [Att25] [Ent23] | Form_33 [Att28] [Ent32] | Label_33 [Att30] [Ent22] | Input_33 [Att31] | Select_33 [Att32] [Ent24] | Textarea_33 [Att36] [Ent2] | Fieldset_33 [Att11] [Ent33] | Legend_33 [Att39] [Ent22] | Button_33 [Att40] [Ent26] | Table_33 [Att41] [Ent34] | PCDATA_33 [Att0] B.ByteString deriving (Show) data Ent34 = Caption_34 [Att11] [Ent22] | Thead_34 [Att42] [Ent35] | Tfoot_34 [Att42] [Ent35] | Tbody_34 [Att42] [Ent35] | Colgroup_34 [Att43] [Ent35] | Col_34 [Att43] | Tr_34 [Att42] [Ent37] deriving (Show) data Ent35 = Tr_35 [Att42] [Ent37] deriving (Show) data Ent36 = Col_36 [Att43] deriving (Show) data Ent37 = Th_37 [Att44] [Ent28] | Td_37 [Att44] [Ent28] deriving (Show) ------------------------- _html :: [Ent0] -> Ent _html = Html [xmlns_att "http://www.w3.org/1999/xhtml"] html_ :: [Att0] -> [Ent0] -> Ent html_ at = Html (xmlns_att "http://www.w3.org/1999/xhtml" :at) class C_Head a b | a -> b where _head :: [b] -> a head_ :: [Att1] -> [b] -> a instance C_Head Ent0 Ent1 where _head r = Head_0 [] ((meta_ [http_equiv_att "Content Type",content_att "text/html;charset=UTF-8"]):r) head_ at r = Head_0 at ((meta_ [http_equiv_att "Content Type",content_att "text/html;charset=UTF-8"]):r) class C_Title a b | a -> b where _title :: [b] -> a title_ :: [Att2] -> [b] -> a instance C_Title Ent1 Ent2 where _title = Title_1 [] title_ = Title_1 class C_Base a where _base :: a base_ :: [Att3] -> a instance C_Base Ent1 where _base = Base_1 [] base_ = Base_1 class C_Meta a where _meta :: a meta_ :: [Att5] -> a instance C_Meta Ent1 where _meta = Meta_1 [] meta_ = Meta_1 class C_Link a where _link :: a link_ :: [Att7] -> a instance C_Link Ent1 where _link = Link_1 [] link_ = Link_1 class C_Style a b | a -> b where _style :: [b] -> a style_ :: [Att8] -> [b] -> a instance C_Style Ent1 Ent2 where _style = Style_1 [] style_ = Style_1 class C_Script a b | a -> b where _script :: [b] -> a script_ :: [Att10] -> [b] -> a instance C_Script Ent1 Ent2 where _script = Script_1 [] script_ = Script_1 instance C_Script Ent3 Ent2 where _script = Script_3 [] script_ = Script_3 instance C_Script Ent4 Ent5 where _script = Script_4 [] script_ = Script_4 instance C_Script Ent6 Ent5 where _script = Script_6 [] script_ = Script_6 instance C_Script Ent7 Ent5 where _script = Script_7 [] script_ = Script_7 instance C_Script Ent10 Ent5 where _script = Script_10 [] script_ = Script_10 instance C_Script Ent11 Ent5 where _script = Script_11 [] script_ = Script_11 instance C_Script Ent12 Ent5 where _script = Script_12 [] script_ = Script_12 instance C_Script Ent17 Ent5 where _script = Script_17 [] script_ = Script_17 instance C_Script Ent18 Ent5 where _script = Script_18 [] script_ = Script_18 instance C_Script Ent21 Ent5 where _script = Script_21 [] script_ = Script_21 instance C_Script Ent22 Ent2 where _script = Script_22 [] script_ = Script_22 instance C_Script Ent23 Ent2 where _script = Script_23 [] script_ = Script_23 instance C_Script Ent26 Ent2 where _script = Script_26 [] script_ = Script_26 instance C_Script Ent27 Ent2 where _script = Script_27 [] script_ = Script_27 instance C_Script Ent28 Ent2 where _script = Script_28 [] script_ = Script_28 instance C_Script Ent31 Ent2 where _script = Script_31 [] script_ = Script_31 instance C_Script Ent32 Ent2 where _script = Script_32 [] script_ = Script_32 instance C_Script Ent33 Ent2 where _script = Script_33 [] script_ = Script_33 class C_Noscript a b | a -> b where _noscript :: [b] -> a noscript_ :: [Att11] -> [b] -> a instance C_Noscript Ent3 Ent27 where _noscript = Noscript_3 [] noscript_ = Noscript_3 instance C_Noscript Ent6 Ent7 where _noscript = Noscript_6 [] noscript_ = Noscript_6 instance C_Noscript Ent7 Ent7 where _noscript = Noscript_7 [] noscript_ = Noscript_7 instance C_Noscript Ent11 Ent7 where _noscript = Noscript_11 [] noscript_ = Noscript_11 instance C_Noscript Ent12 Ent7 where _noscript = Noscript_12 [] noscript_ = Noscript_12 instance C_Noscript Ent17 Ent7 where _noscript = Noscript_17 [] noscript_ = Noscript_17 instance C_Noscript Ent18 Ent7 where _noscript = Noscript_18 [] noscript_ = Noscript_18 instance C_Noscript Ent21 Ent7 where _noscript = Noscript_21 [] noscript_ = Noscript_21 instance C_Noscript Ent23 Ent27 where _noscript = Noscript_23 [] noscript_ = Noscript_23 instance C_Noscript Ent26 Ent27 where _noscript = Noscript_26 [] noscript_ = Noscript_26 instance C_Noscript Ent27 Ent27 where _noscript = Noscript_27 [] noscript_ = Noscript_27 instance C_Noscript Ent28 Ent27 where _noscript = Noscript_28 [] noscript_ = Noscript_28 instance C_Noscript Ent32 Ent27 where _noscript = Noscript_32 [] noscript_ = Noscript_32 instance C_Noscript Ent33 Ent27 where _noscript = Noscript_33 [] noscript_ = Noscript_33 class C_Body a b | a -> b where _body :: [b] -> a body_ :: [Att12] -> [b] -> a instance C_Body Ent0 Ent27 where _body = Body_0 [] body_ = Body_0 class C_Div a b | a -> b where _div :: [b] -> a div_ :: [Att11] -> [b] -> a instance C_Div Ent3 Ent28 where _div = Div_3 [] div_ = Div_3 instance C_Div Ent6 Ent6 where _div = Div_6 [] div_ = Div_6 instance C_Div Ent7 Ent6 where _div = Div_7 [] div_ = Div_7 instance C_Div Ent11 Ent6 where _div = Div_11 [] div_ = Div_11 instance C_Div Ent12 Ent6 where _div = Div_12 [] div_ = Div_12 instance C_Div Ent17 Ent6 where _div = Div_17 [] div_ = Div_17 instance C_Div Ent18 Ent6 where _div = Div_18 [] div_ = Div_18 instance C_Div Ent21 Ent6 where _div = Div_21 [] div_ = Div_21 instance C_Div Ent23 Ent28 where _div = Div_23 [] div_ = Div_23 instance C_Div Ent26 Ent28 where _div = Div_26 [] div_ = Div_26 instance C_Div Ent27 Ent28 where _div = Div_27 [] div_ = Div_27 instance C_Div Ent28 Ent28 where _div = Div_28 [] div_ = Div_28 instance C_Div Ent32 Ent28 where _div = Div_32 [] div_ = Div_32 instance C_Div Ent33 Ent28 where _div = Div_33 [] div_ = Div_33 class C_P a b | a -> b where _p :: [b] -> a p_ :: [Att11] -> [b] -> a instance C_P Ent3 Ent22 where _p = P_3 [] p_ = P_3 instance C_P Ent6 Ent4 where _p = P_6 [] p_ = P_6 instance C_P Ent7 Ent4 where _p = P_7 [] p_ = P_7 instance C_P Ent11 Ent4 where _p = P_11 [] p_ = P_11 instance C_P Ent12 Ent4 where _p = P_12 [] p_ = P_12 instance C_P Ent17 Ent4 where _p = P_17 [] p_ = P_17 instance C_P Ent18 Ent4 where _p = P_18 [] p_ = P_18 instance C_P Ent21 Ent4 where _p = P_21 [] p_ = P_21 instance C_P Ent23 Ent22 where _p = P_23 [] p_ = P_23 instance C_P Ent26 Ent22 where _p = P_26 [] p_ = P_26 instance C_P Ent27 Ent22 where _p = P_27 [] p_ = P_27 instance C_P Ent28 Ent22 where _p = P_28 [] p_ = P_28 instance C_P Ent32 Ent22 where _p = P_32 [] p_ = P_32 instance C_P Ent33 Ent22 where _p = P_33 [] p_ = P_33 class C_H1 a b | a -> b where _h1 :: [b] -> a h1_ :: [Att11] -> [b] -> a instance C_H1 Ent3 Ent22 where _h1 = H1_3 [] h1_ = H1_3 instance C_H1 Ent6 Ent4 where _h1 = H1_6 [] h1_ = H1_6 instance C_H1 Ent7 Ent4 where _h1 = H1_7 [] h1_ = H1_7 instance C_H1 Ent11 Ent4 where _h1 = H1_11 [] h1_ = H1_11 instance C_H1 Ent12 Ent4 where _h1 = H1_12 [] h1_ = H1_12 instance C_H1 Ent17 Ent4 where _h1 = H1_17 [] h1_ = H1_17 instance C_H1 Ent18 Ent4 where _h1 = H1_18 [] h1_ = H1_18 instance C_H1 Ent21 Ent4 where _h1 = H1_21 [] h1_ = H1_21 instance C_H1 Ent23 Ent22 where _h1 = H1_23 [] h1_ = H1_23 instance C_H1 Ent26 Ent22 where _h1 = H1_26 [] h1_ = H1_26 instance C_H1 Ent27 Ent22 where _h1 = H1_27 [] h1_ = H1_27 instance C_H1 Ent28 Ent22 where _h1 = H1_28 [] h1_ = H1_28 instance C_H1 Ent32 Ent22 where _h1 = H1_32 [] h1_ = H1_32 instance C_H1 Ent33 Ent22 where _h1 = H1_33 [] h1_ = H1_33 class C_H2 a b | a -> b where _h2 :: [b] -> a h2_ :: [Att11] -> [b] -> a instance C_H2 Ent3 Ent22 where _h2 = H2_3 [] h2_ = H2_3 instance C_H2 Ent6 Ent4 where _h2 = H2_6 [] h2_ = H2_6 instance C_H2 Ent7 Ent4 where _h2 = H2_7 [] h2_ = H2_7 instance C_H2 Ent11 Ent4 where _h2 = H2_11 [] h2_ = H2_11 instance C_H2 Ent12 Ent4 where _h2 = H2_12 [] h2_ = H2_12 instance C_H2 Ent17 Ent4 where _h2 = H2_17 [] h2_ = H2_17 instance C_H2 Ent18 Ent4 where _h2 = H2_18 [] h2_ = H2_18 instance C_H2 Ent21 Ent4 where _h2 = H2_21 [] h2_ = H2_21 instance C_H2 Ent23 Ent22 where _h2 = H2_23 [] h2_ = H2_23 instance C_H2 Ent26 Ent22 where _h2 = H2_26 [] h2_ = H2_26 instance C_H2 Ent27 Ent22 where _h2 = H2_27 [] h2_ = H2_27 instance C_H2 Ent28 Ent22 where _h2 = H2_28 [] h2_ = H2_28 instance C_H2 Ent32 Ent22 where _h2 = H2_32 [] h2_ = H2_32 instance C_H2 Ent33 Ent22 where _h2 = H2_33 [] h2_ = H2_33 class C_H3 a b | a -> b where _h3 :: [b] -> a h3_ :: [Att11] -> [b] -> a instance C_H3 Ent3 Ent22 where _h3 = H3_3 [] h3_ = H3_3 instance C_H3 Ent6 Ent4 where _h3 = H3_6 [] h3_ = H3_6 instance C_H3 Ent7 Ent4 where _h3 = H3_7 [] h3_ = H3_7 instance C_H3 Ent11 Ent4 where _h3 = H3_11 [] h3_ = H3_11 instance C_H3 Ent12 Ent4 where _h3 = H3_12 [] h3_ = H3_12 instance C_H3 Ent17 Ent4 where _h3 = H3_17 [] h3_ = H3_17 instance C_H3 Ent18 Ent4 where _h3 = H3_18 [] h3_ = H3_18 instance C_H3 Ent21 Ent4 where _h3 = H3_21 [] h3_ = H3_21 instance C_H3 Ent23 Ent22 where _h3 = H3_23 [] h3_ = H3_23 instance C_H3 Ent26 Ent22 where _h3 = H3_26 [] h3_ = H3_26 instance C_H3 Ent27 Ent22 where _h3 = H3_27 [] h3_ = H3_27 instance C_H3 Ent28 Ent22 where _h3 = H3_28 [] h3_ = H3_28 instance C_H3 Ent32 Ent22 where _h3 = H3_32 [] h3_ = H3_32 instance C_H3 Ent33 Ent22 where _h3 = H3_33 [] h3_ = H3_33 class C_H4 a b | a -> b where _h4 :: [b] -> a h4_ :: [Att11] -> [b] -> a instance C_H4 Ent3 Ent22 where _h4 = H4_3 [] h4_ = H4_3 instance C_H4 Ent6 Ent4 where _h4 = H4_6 [] h4_ = H4_6 instance C_H4 Ent7 Ent4 where _h4 = H4_7 [] h4_ = H4_7 instance C_H4 Ent11 Ent4 where _h4 = H4_11 [] h4_ = H4_11 instance C_H4 Ent12 Ent4 where _h4 = H4_12 [] h4_ = H4_12 instance C_H4 Ent17 Ent4 where _h4 = H4_17 [] h4_ = H4_17 instance C_H4 Ent18 Ent4 where _h4 = H4_18 [] h4_ = H4_18 instance C_H4 Ent21 Ent4 where _h4 = H4_21 [] h4_ = H4_21 instance C_H4 Ent23 Ent22 where _h4 = H4_23 [] h4_ = H4_23 instance C_H4 Ent26 Ent22 where _h4 = H4_26 [] h4_ = H4_26 instance C_H4 Ent27 Ent22 where _h4 = H4_27 [] h4_ = H4_27 instance C_H4 Ent28 Ent22 where _h4 = H4_28 [] h4_ = H4_28 instance C_H4 Ent32 Ent22 where _h4 = H4_32 [] h4_ = H4_32 instance C_H4 Ent33 Ent22 where _h4 = H4_33 [] h4_ = H4_33 class C_H5 a b | a -> b where _h5 :: [b] -> a h5_ :: [Att11] -> [b] -> a instance C_H5 Ent3 Ent22 where _h5 = H5_3 [] h5_ = H5_3 instance C_H5 Ent6 Ent4 where _h5 = H5_6 [] h5_ = H5_6 instance C_H5 Ent7 Ent4 where _h5 = H5_7 [] h5_ = H5_7 instance C_H5 Ent11 Ent4 where _h5 = H5_11 [] h5_ = H5_11 instance C_H5 Ent12 Ent4 where _h5 = H5_12 [] h5_ = H5_12 instance C_H5 Ent17 Ent4 where _h5 = H5_17 [] h5_ = H5_17 instance C_H5 Ent18 Ent4 where _h5 = H5_18 [] h5_ = H5_18 instance C_H5 Ent21 Ent4 where _h5 = H5_21 [] h5_ = H5_21 instance C_H5 Ent23 Ent22 where _h5 = H5_23 [] h5_ = H5_23 instance C_H5 Ent26 Ent22 where _h5 = H5_26 [] h5_ = H5_26 instance C_H5 Ent27 Ent22 where _h5 = H5_27 [] h5_ = H5_27 instance C_H5 Ent28 Ent22 where _h5 = H5_28 [] h5_ = H5_28 instance C_H5 Ent32 Ent22 where _h5 = H5_32 [] h5_ = H5_32 instance C_H5 Ent33 Ent22 where _h5 = H5_33 [] h5_ = H5_33 class C_H6 a b | a -> b where _h6 :: [b] -> a h6_ :: [Att11] -> [b] -> a instance C_H6 Ent3 Ent22 where _h6 = H6_3 [] h6_ = H6_3 instance C_H6 Ent6 Ent4 where _h6 = H6_6 [] h6_ = H6_6 instance C_H6 Ent7 Ent4 where _h6 = H6_7 [] h6_ = H6_7 instance C_H6 Ent11 Ent4 where _h6 = H6_11 [] h6_ = H6_11 instance C_H6 Ent12 Ent4 where _h6 = H6_12 [] h6_ = H6_12 instance C_H6 Ent17 Ent4 where _h6 = H6_17 [] h6_ = H6_17 instance C_H6 Ent18 Ent4 where _h6 = H6_18 [] h6_ = H6_18 instance C_H6 Ent21 Ent4 where _h6 = H6_21 [] h6_ = H6_21 instance C_H6 Ent23 Ent22 where _h6 = H6_23 [] h6_ = H6_23 instance C_H6 Ent26 Ent22 where _h6 = H6_26 [] h6_ = H6_26 instance C_H6 Ent27 Ent22 where _h6 = H6_27 [] h6_ = H6_27 instance C_H6 Ent28 Ent22 where _h6 = H6_28 [] h6_ = H6_28 instance C_H6 Ent32 Ent22 where _h6 = H6_32 [] h6_ = H6_32 instance C_H6 Ent33 Ent22 where _h6 = H6_33 [] h6_ = H6_33 class C_Ul a b | a -> b where _ul :: [b] -> a ul_ :: [Att11] -> [b] -> a instance C_Ul Ent3 Ent29 where _ul = Ul_3 [] ul_ = Ul_3 instance C_Ul Ent6 Ent8 where _ul = Ul_6 [] ul_ = Ul_6 instance C_Ul Ent7 Ent8 where _ul = Ul_7 [] ul_ = Ul_7 instance C_Ul Ent11 Ent8 where _ul = Ul_11 [] ul_ = Ul_11 instance C_Ul Ent12 Ent8 where _ul = Ul_12 [] ul_ = Ul_12 instance C_Ul Ent17 Ent8 where _ul = Ul_17 [] ul_ = Ul_17 instance C_Ul Ent18 Ent8 where _ul = Ul_18 [] ul_ = Ul_18 instance C_Ul Ent21 Ent8 where _ul = Ul_21 [] ul_ = Ul_21 instance C_Ul Ent23 Ent29 where _ul = Ul_23 [] ul_ = Ul_23 instance C_Ul Ent26 Ent29 where _ul = Ul_26 [] ul_ = Ul_26 instance C_Ul Ent27 Ent29 where _ul = Ul_27 [] ul_ = Ul_27 instance C_Ul Ent28 Ent29 where _ul = Ul_28 [] ul_ = Ul_28 instance C_Ul Ent32 Ent29 where _ul = Ul_32 [] ul_ = Ul_32 instance C_Ul Ent33 Ent29 where _ul = Ul_33 [] ul_ = Ul_33 class C_Ol a b | a -> b where _ol :: [b] -> a ol_ :: [Att11] -> [b] -> a instance C_Ol Ent3 Ent29 where _ol = Ol_3 [] ol_ = Ol_3 instance C_Ol Ent6 Ent8 where _ol = Ol_6 [] ol_ = Ol_6 instance C_Ol Ent7 Ent8 where _ol = Ol_7 [] ol_ = Ol_7 instance C_Ol Ent11 Ent8 where _ol = Ol_11 [] ol_ = Ol_11 instance C_Ol Ent12 Ent8 where _ol = Ol_12 [] ol_ = Ol_12 instance C_Ol Ent17 Ent8 where _ol = Ol_17 [] ol_ = Ol_17 instance C_Ol Ent18 Ent8 where _ol = Ol_18 [] ol_ = Ol_18 instance C_Ol Ent21 Ent8 where _ol = Ol_21 [] ol_ = Ol_21 instance C_Ol Ent23 Ent29 where _ol = Ol_23 [] ol_ = Ol_23 instance C_Ol Ent26 Ent29 where _ol = Ol_26 [] ol_ = Ol_26 instance C_Ol Ent27 Ent29 where _ol = Ol_27 [] ol_ = Ol_27 instance C_Ol Ent28 Ent29 where _ol = Ol_28 [] ol_ = Ol_28 instance C_Ol Ent32 Ent29 where _ol = Ol_32 [] ol_ = Ol_32 instance C_Ol Ent33 Ent29 where _ol = Ol_33 [] ol_ = Ol_33 class C_Li a b | a -> b where _li :: [b] -> a li_ :: [Att11] -> [b] -> a instance C_Li Ent8 Ent6 where _li = Li_8 [] li_ = Li_8 instance C_Li Ent29 Ent28 where _li = Li_29 [] li_ = Li_29 class C_Dl a b | a -> b where _dl :: [b] -> a dl_ :: [Att11] -> [b] -> a instance C_Dl Ent3 Ent30 where _dl = Dl_3 [] dl_ = Dl_3 instance C_Dl Ent6 Ent9 where _dl = Dl_6 [] dl_ = Dl_6 instance C_Dl Ent7 Ent9 where _dl = Dl_7 [] dl_ = Dl_7 instance C_Dl Ent11 Ent9 where _dl = Dl_11 [] dl_ = Dl_11 instance C_Dl Ent12 Ent9 where _dl = Dl_12 [] dl_ = Dl_12 instance C_Dl Ent17 Ent9 where _dl = Dl_17 [] dl_ = Dl_17 instance C_Dl Ent18 Ent9 where _dl = Dl_18 [] dl_ = Dl_18 instance C_Dl Ent21 Ent9 where _dl = Dl_21 [] dl_ = Dl_21 instance C_Dl Ent23 Ent30 where _dl = Dl_23 [] dl_ = Dl_23 instance C_Dl Ent26 Ent30 where _dl = Dl_26 [] dl_ = Dl_26 instance C_Dl Ent27 Ent30 where _dl = Dl_27 [] dl_ = Dl_27 instance C_Dl Ent28 Ent30 where _dl = Dl_28 [] dl_ = Dl_28 instance C_Dl Ent32 Ent30 where _dl = Dl_32 [] dl_ = Dl_32 instance C_Dl Ent33 Ent30 where _dl = Dl_33 [] dl_ = Dl_33 class C_Dt a b | a -> b where _dt :: [b] -> a dt_ :: [Att11] -> [b] -> a instance C_Dt Ent9 Ent4 where _dt = Dt_9 [] dt_ = Dt_9 instance C_Dt Ent30 Ent22 where _dt = Dt_30 [] dt_ = Dt_30 class C_Dd a b | a -> b where _dd :: [b] -> a dd_ :: [Att11] -> [b] -> a instance C_Dd Ent9 Ent6 where _dd = Dd_9 [] dd_ = Dd_9 instance C_Dd Ent30 Ent28 where _dd = Dd_30 [] dd_ = Dd_30 class C_Address a b | a -> b where _address :: [b] -> a address_ :: [Att11] -> [b] -> a instance C_Address Ent3 Ent22 where _address = Address_3 [] address_ = Address_3 instance C_Address Ent6 Ent4 where _address = Address_6 [] address_ = Address_6 instance C_Address Ent7 Ent4 where _address = Address_7 [] address_ = Address_7 instance C_Address Ent11 Ent4 where _address = Address_11 [] address_ = Address_11 instance C_Address Ent12 Ent4 where _address = Address_12 [] address_ = Address_12 instance C_Address Ent17 Ent4 where _address = Address_17 [] address_ = Address_17 instance C_Address Ent18 Ent4 where _address = Address_18 [] address_ = Address_18 instance C_Address Ent21 Ent4 where _address = Address_21 [] address_ = Address_21 instance C_Address Ent23 Ent22 where _address = Address_23 [] address_ = Address_23 instance C_Address Ent26 Ent22 where _address = Address_26 [] address_ = Address_26 instance C_Address Ent27 Ent22 where _address = Address_27 [] address_ = Address_27 instance C_Address Ent28 Ent22 where _address = Address_28 [] address_ = Address_28 instance C_Address Ent32 Ent22 where _address = Address_32 [] address_ = Address_32 instance C_Address Ent33 Ent22 where _address = Address_33 [] address_ = Address_33 class C_Hr a where _hr :: a hr_ :: [Att11] -> a instance C_Hr Ent3 where _hr = Hr_3 [] hr_ = Hr_3 instance C_Hr Ent6 where _hr = Hr_6 [] hr_ = Hr_6 instance C_Hr Ent7 where _hr = Hr_7 [] hr_ = Hr_7 instance C_Hr Ent11 where _hr = Hr_11 [] hr_ = Hr_11 instance C_Hr Ent12 where _hr = Hr_12 [] hr_ = Hr_12 instance C_Hr Ent17 where _hr = Hr_17 [] hr_ = Hr_17 instance C_Hr Ent18 where _hr = Hr_18 [] hr_ = Hr_18 instance C_Hr Ent21 where _hr = Hr_21 [] hr_ = Hr_21 instance C_Hr Ent23 where _hr = Hr_23 [] hr_ = Hr_23 instance C_Hr Ent26 where _hr = Hr_26 [] hr_ = Hr_26 instance C_Hr Ent27 where _hr = Hr_27 [] hr_ = Hr_27 instance C_Hr Ent28 where _hr = Hr_28 [] hr_ = Hr_28 instance C_Hr Ent32 where _hr = Hr_32 [] hr_ = Hr_32 instance C_Hr Ent33 where _hr = Hr_33 [] hr_ = Hr_33 class C_Pre a b | a -> b where _pre :: [b] -> a pre_ :: [Att13] -> [b] -> a instance C_Pre Ent3 Ent31 where _pre = Pre_3 [] pre_ = Pre_3 instance C_Pre Ent6 Ent10 where _pre = Pre_6 [] pre_ = Pre_6 instance C_Pre Ent7 Ent10 where _pre = Pre_7 [] pre_ = Pre_7 instance C_Pre Ent11 Ent10 where _pre = Pre_11 [] pre_ = Pre_11 instance C_Pre Ent12 Ent10 where _pre = Pre_12 [] pre_ = Pre_12 instance C_Pre Ent17 Ent10 where _pre = Pre_17 [] pre_ = Pre_17 instance C_Pre Ent18 Ent10 where _pre = Pre_18 [] pre_ = Pre_18 instance C_Pre Ent21 Ent10 where _pre = Pre_21 [] pre_ = Pre_21 instance C_Pre Ent23 Ent31 where _pre = Pre_23 [] pre_ = Pre_23 instance C_Pre Ent26 Ent31 where _pre = Pre_26 [] pre_ = Pre_26 instance C_Pre Ent27 Ent31 where _pre = Pre_27 [] pre_ = Pre_27 instance C_Pre Ent28 Ent31 where _pre = Pre_28 [] pre_ = Pre_28 instance C_Pre Ent32 Ent31 where _pre = Pre_32 [] pre_ = Pre_32 instance C_Pre Ent33 Ent31 where _pre = Pre_33 [] pre_ = Pre_33 class C_Blockquote a b | a -> b where _blockquote :: [b] -> a blockquote_ :: [Att14] -> [b] -> a instance C_Blockquote Ent3 Ent27 where _blockquote = Blockquote_3 [] blockquote_ = Blockquote_3 instance C_Blockquote Ent6 Ent7 where _blockquote = Blockquote_6 [] blockquote_ = Blockquote_6 instance C_Blockquote Ent7 Ent7 where _blockquote = Blockquote_7 [] blockquote_ = Blockquote_7 instance C_Blockquote Ent11 Ent7 where _blockquote = Blockquote_11 [] blockquote_ = Blockquote_11 instance C_Blockquote Ent12 Ent7 where _blockquote = Blockquote_12 [] blockquote_ = Blockquote_12 instance C_Blockquote Ent17 Ent7 where _blockquote = Blockquote_17 [] blockquote_ = Blockquote_17 instance C_Blockquote Ent18 Ent7 where _blockquote = Blockquote_18 [] blockquote_ = Blockquote_18 instance C_Blockquote Ent21 Ent7 where _blockquote = Blockquote_21 [] blockquote_ = Blockquote_21 instance C_Blockquote Ent23 Ent27 where _blockquote = Blockquote_23 [] blockquote_ = Blockquote_23 instance C_Blockquote Ent26 Ent27 where _blockquote = Blockquote_26 [] blockquote_ = Blockquote_26 instance C_Blockquote Ent27 Ent27 where _blockquote = Blockquote_27 [] blockquote_ = Blockquote_27 instance C_Blockquote Ent28 Ent27 where _blockquote = Blockquote_28 [] blockquote_ = Blockquote_28 instance C_Blockquote Ent32 Ent27 where _blockquote = Blockquote_32 [] blockquote_ = Blockquote_32 instance C_Blockquote Ent33 Ent27 where _blockquote = Blockquote_33 [] blockquote_ = Blockquote_33 class C_Ins a b | a -> b where _ins :: [b] -> a ins_ :: [Att15] -> [b] -> a instance C_Ins Ent3 Ent28 where _ins = Ins_3 [] ins_ = Ins_3 instance C_Ins Ent4 Ent6 where _ins = Ins_4 [] ins_ = Ins_4 instance C_Ins Ent6 Ent6 where _ins = Ins_6 [] ins_ = Ins_6 instance C_Ins Ent7 Ent6 where _ins = Ins_7 [] ins_ = Ins_7 instance C_Ins Ent10 Ent6 where _ins = Ins_10 [] ins_ = Ins_10 instance C_Ins Ent11 Ent6 where _ins = Ins_11 [] ins_ = Ins_11 instance C_Ins Ent12 Ent6 where _ins = Ins_12 [] ins_ = Ins_12 instance C_Ins Ent17 Ent6 where _ins = Ins_17 [] ins_ = Ins_17 instance C_Ins Ent18 Ent6 where _ins = Ins_18 [] ins_ = Ins_18 instance C_Ins Ent21 Ent6 where _ins = Ins_21 [] ins_ = Ins_21 instance C_Ins Ent22 Ent28 where _ins = Ins_22 [] ins_ = Ins_22 instance C_Ins Ent23 Ent28 where _ins = Ins_23 [] ins_ = Ins_23 instance C_Ins Ent26 Ent28 where _ins = Ins_26 [] ins_ = Ins_26 instance C_Ins Ent27 Ent28 where _ins = Ins_27 [] ins_ = Ins_27 instance C_Ins Ent28 Ent28 where _ins = Ins_28 [] ins_ = Ins_28 instance C_Ins Ent31 Ent28 where _ins = Ins_31 [] ins_ = Ins_31 instance C_Ins Ent32 Ent28 where _ins = Ins_32 [] ins_ = Ins_32 instance C_Ins Ent33 Ent28 where _ins = Ins_33 [] ins_ = Ins_33 class C_Del a b | a -> b where _del :: [b] -> a del_ :: [Att15] -> [b] -> a instance C_Del Ent3 Ent28 where _del = Del_3 [] del_ = Del_3 instance C_Del Ent4 Ent6 where _del = Del_4 [] del_ = Del_4 instance C_Del Ent6 Ent6 where _del = Del_6 [] del_ = Del_6 instance C_Del Ent7 Ent6 where _del = Del_7 [] del_ = Del_7 instance C_Del Ent10 Ent6 where _del = Del_10 [] del_ = Del_10 instance C_Del Ent11 Ent6 where _del = Del_11 [] del_ = Del_11 instance C_Del Ent12 Ent6 where _del = Del_12 [] del_ = Del_12 instance C_Del Ent17 Ent6 where _del = Del_17 [] del_ = Del_17 instance C_Del Ent18 Ent6 where _del = Del_18 [] del_ = Del_18 instance C_Del Ent21 Ent6 where _del = Del_21 [] del_ = Del_21 instance C_Del Ent22 Ent28 where _del = Del_22 [] del_ = Del_22 instance C_Del Ent23 Ent28 where _del = Del_23 [] del_ = Del_23 instance C_Del Ent26 Ent28 where _del = Del_26 [] del_ = Del_26 instance C_Del Ent27 Ent28 where _del = Del_27 [] del_ = Del_27 instance C_Del Ent28 Ent28 where _del = Del_28 [] del_ = Del_28 instance C_Del Ent31 Ent28 where _del = Del_31 [] del_ = Del_31 instance C_Del Ent32 Ent28 where _del = Del_32 [] del_ = Del_32 instance C_Del Ent33 Ent28 where _del = Del_33 [] del_ = Del_33 class C_A a b | a -> b where _a :: [b] -> a a_ :: [Att16] -> [b] -> a instance C_A Ent3 Ent4 where _a = A_3 [] a_ = A_3 instance C_A Ent22 Ent4 where _a = A_22 [] a_ = A_22 instance C_A Ent28 Ent4 where _a = A_28 [] a_ = A_28 instance C_A Ent31 Ent4 where _a = A_31 [] a_ = A_31 instance C_A Ent33 Ent4 where _a = A_33 [] a_ = A_33 class C_Span a b | a -> b where _span :: [b] -> a span_ :: [Att11] -> [b] -> a instance C_Span Ent3 Ent22 where _span = Span_3 [] span_ = Span_3 instance C_Span Ent4 Ent4 where _span = Span_4 [] span_ = Span_4 instance C_Span Ent6 Ent4 where _span = Span_6 [] span_ = Span_6 instance C_Span Ent10 Ent4 where _span = Span_10 [] span_ = Span_10 instance C_Span Ent12 Ent4 where _span = Span_12 [] span_ = Span_12 instance C_Span Ent17 Ent4 where _span = Span_17 [] span_ = Span_17 instance C_Span Ent21 Ent4 where _span = Span_21 [] span_ = Span_21 instance C_Span Ent22 Ent22 where _span = Span_22 [] span_ = Span_22 instance C_Span Ent26 Ent22 where _span = Span_26 [] span_ = Span_26 instance C_Span Ent28 Ent22 where _span = Span_28 [] span_ = Span_28 instance C_Span Ent31 Ent22 where _span = Span_31 [] span_ = Span_31 instance C_Span Ent33 Ent22 where _span = Span_33 [] span_ = Span_33 class C_Bdo a b | a -> b where _bdo :: [b] -> a bdo_ :: [Att11] -> [b] -> a instance C_Bdo Ent3 Ent22 where _bdo = Bdo_3 [] bdo_ = Bdo_3 instance C_Bdo Ent4 Ent4 where _bdo = Bdo_4 [] bdo_ = Bdo_4 instance C_Bdo Ent6 Ent4 where _bdo = Bdo_6 [] bdo_ = Bdo_6 instance C_Bdo Ent10 Ent4 where _bdo = Bdo_10 [] bdo_ = Bdo_10 instance C_Bdo Ent12 Ent4 where _bdo = Bdo_12 [] bdo_ = Bdo_12 instance C_Bdo Ent17 Ent4 where _bdo = Bdo_17 [] bdo_ = Bdo_17 instance C_Bdo Ent21 Ent4 where _bdo = Bdo_21 [] bdo_ = Bdo_21 instance C_Bdo Ent22 Ent22 where _bdo = Bdo_22 [] bdo_ = Bdo_22 instance C_Bdo Ent26 Ent22 where _bdo = Bdo_26 [] bdo_ = Bdo_26 instance C_Bdo Ent28 Ent22 where _bdo = Bdo_28 [] bdo_ = Bdo_28 instance C_Bdo Ent31 Ent22 where _bdo = Bdo_31 [] bdo_ = Bdo_31 instance C_Bdo Ent33 Ent22 where _bdo = Bdo_33 [] bdo_ = Bdo_33 class C_Br a where _br :: a br_ :: [Att19] -> a instance C_Br Ent3 where _br = Br_3 [] br_ = Br_3 instance C_Br Ent4 where _br = Br_4 [] br_ = Br_4 instance C_Br Ent6 where _br = Br_6 [] br_ = Br_6 instance C_Br Ent10 where _br = Br_10 [] br_ = Br_10 instance C_Br Ent12 where _br = Br_12 [] br_ = Br_12 instance C_Br Ent17 where _br = Br_17 [] br_ = Br_17 instance C_Br Ent21 where _br = Br_21 [] br_ = Br_21 instance C_Br Ent22 where _br = Br_22 [] br_ = Br_22 instance C_Br Ent26 where _br = Br_26 [] br_ = Br_26 instance C_Br Ent28 where _br = Br_28 [] br_ = Br_28 instance C_Br Ent31 where _br = Br_31 [] br_ = Br_31 instance C_Br Ent33 where _br = Br_33 [] br_ = Br_33 class C_Em a b | a -> b where _em :: [b] -> a em_ :: [Att11] -> [b] -> a instance C_Em Ent3 Ent22 where _em = Em_3 [] em_ = Em_3 instance C_Em Ent4 Ent4 where _em = Em_4 [] em_ = Em_4 instance C_Em Ent6 Ent4 where _em = Em_6 [] em_ = Em_6 instance C_Em Ent10 Ent4 where _em = Em_10 [] em_ = Em_10 instance C_Em Ent12 Ent4 where _em = Em_12 [] em_ = Em_12 instance C_Em Ent17 Ent4 where _em = Em_17 [] em_ = Em_17 instance C_Em Ent21 Ent4 where _em = Em_21 [] em_ = Em_21 instance C_Em Ent22 Ent22 where _em = Em_22 [] em_ = Em_22 instance C_Em Ent26 Ent22 where _em = Em_26 [] em_ = Em_26 instance C_Em Ent28 Ent22 where _em = Em_28 [] em_ = Em_28 instance C_Em Ent31 Ent22 where _em = Em_31 [] em_ = Em_31 instance C_Em Ent33 Ent22 where _em = Em_33 [] em_ = Em_33 class C_Strong a b | a -> b where _strong :: [b] -> a strong_ :: [Att11] -> [b] -> a instance C_Strong Ent3 Ent22 where _strong = Strong_3 [] strong_ = Strong_3 instance C_Strong Ent4 Ent4 where _strong = Strong_4 [] strong_ = Strong_4 instance C_Strong Ent6 Ent4 where _strong = Strong_6 [] strong_ = Strong_6 instance C_Strong Ent10 Ent4 where _strong = Strong_10 [] strong_ = Strong_10 instance C_Strong Ent12 Ent4 where _strong = Strong_12 [] strong_ = Strong_12 instance C_Strong Ent17 Ent4 where _strong = Strong_17 [] strong_ = Strong_17 instance C_Strong Ent21 Ent4 where _strong = Strong_21 [] strong_ = Strong_21 instance C_Strong Ent22 Ent22 where _strong = Strong_22 [] strong_ = Strong_22 instance C_Strong Ent26 Ent22 where _strong = Strong_26 [] strong_ = Strong_26 instance C_Strong Ent28 Ent22 where _strong = Strong_28 [] strong_ = Strong_28 instance C_Strong Ent31 Ent22 where _strong = Strong_31 [] strong_ = Strong_31 instance C_Strong Ent33 Ent22 where _strong = Strong_33 [] strong_ = Strong_33 class C_Dfn a b | a -> b where _dfn :: [b] -> a dfn_ :: [Att11] -> [b] -> a instance C_Dfn Ent3 Ent22 where _dfn = Dfn_3 [] dfn_ = Dfn_3 instance C_Dfn Ent4 Ent4 where _dfn = Dfn_4 [] dfn_ = Dfn_4 instance C_Dfn Ent6 Ent4 where _dfn = Dfn_6 [] dfn_ = Dfn_6 instance C_Dfn Ent10 Ent4 where _dfn = Dfn_10 [] dfn_ = Dfn_10 instance C_Dfn Ent12 Ent4 where _dfn = Dfn_12 [] dfn_ = Dfn_12 instance C_Dfn Ent17 Ent4 where _dfn = Dfn_17 [] dfn_ = Dfn_17 instance C_Dfn Ent21 Ent4 where _dfn = Dfn_21 [] dfn_ = Dfn_21 instance C_Dfn Ent22 Ent22 where _dfn = Dfn_22 [] dfn_ = Dfn_22 instance C_Dfn Ent26 Ent22 where _dfn = Dfn_26 [] dfn_ = Dfn_26 instance C_Dfn Ent28 Ent22 where _dfn = Dfn_28 [] dfn_ = Dfn_28 instance C_Dfn Ent31 Ent22 where _dfn = Dfn_31 [] dfn_ = Dfn_31 instance C_Dfn Ent33 Ent22 where _dfn = Dfn_33 [] dfn_ = Dfn_33 class C_Code a b | a -> b where _code :: [b] -> a code_ :: [Att11] -> [b] -> a instance C_Code Ent3 Ent22 where _code = Code_3 [] code_ = Code_3 instance C_Code Ent4 Ent4 where _code = Code_4 [] code_ = Code_4 instance C_Code Ent6 Ent4 where _code = Code_6 [] code_ = Code_6 instance C_Code Ent10 Ent4 where _code = Code_10 [] code_ = Code_10 instance C_Code Ent12 Ent4 where _code = Code_12 [] code_ = Code_12 instance C_Code Ent17 Ent4 where _code = Code_17 [] code_ = Code_17 instance C_Code Ent21 Ent4 where _code = Code_21 [] code_ = Code_21 instance C_Code Ent22 Ent22 where _code = Code_22 [] code_ = Code_22 instance C_Code Ent26 Ent22 where _code = Code_26 [] code_ = Code_26 instance C_Code Ent28 Ent22 where _code = Code_28 [] code_ = Code_28 instance C_Code Ent31 Ent22 where _code = Code_31 [] code_ = Code_31 instance C_Code Ent33 Ent22 where _code = Code_33 [] code_ = Code_33 class C_Samp a b | a -> b where _samp :: [b] -> a samp_ :: [Att11] -> [b] -> a instance C_Samp Ent3 Ent22 where _samp = Samp_3 [] samp_ = Samp_3 instance C_Samp Ent4 Ent4 where _samp = Samp_4 [] samp_ = Samp_4 instance C_Samp Ent6 Ent4 where _samp = Samp_6 [] samp_ = Samp_6 instance C_Samp Ent10 Ent4 where _samp = Samp_10 [] samp_ = Samp_10 instance C_Samp Ent12 Ent4 where _samp = Samp_12 [] samp_ = Samp_12 instance C_Samp Ent17 Ent4 where _samp = Samp_17 [] samp_ = Samp_17 instance C_Samp Ent21 Ent4 where _samp = Samp_21 [] samp_ = Samp_21 instance C_Samp Ent22 Ent22 where _samp = Samp_22 [] samp_ = Samp_22 instance C_Samp Ent26 Ent22 where _samp = Samp_26 [] samp_ = Samp_26 instance C_Samp Ent28 Ent22 where _samp = Samp_28 [] samp_ = Samp_28 instance C_Samp Ent31 Ent22 where _samp = Samp_31 [] samp_ = Samp_31 instance C_Samp Ent33 Ent22 where _samp = Samp_33 [] samp_ = Samp_33 class C_Kbd a b | a -> b where _kbd :: [b] -> a kbd_ :: [Att11] -> [b] -> a instance C_Kbd Ent3 Ent22 where _kbd = Kbd_3 [] kbd_ = Kbd_3 instance C_Kbd Ent4 Ent4 where _kbd = Kbd_4 [] kbd_ = Kbd_4 instance C_Kbd Ent6 Ent4 where _kbd = Kbd_6 [] kbd_ = Kbd_6 instance C_Kbd Ent10 Ent4 where _kbd = Kbd_10 [] kbd_ = Kbd_10 instance C_Kbd Ent12 Ent4 where _kbd = Kbd_12 [] kbd_ = Kbd_12 instance C_Kbd Ent17 Ent4 where _kbd = Kbd_17 [] kbd_ = Kbd_17 instance C_Kbd Ent21 Ent4 where _kbd = Kbd_21 [] kbd_ = Kbd_21 instance C_Kbd Ent22 Ent22 where _kbd = Kbd_22 [] kbd_ = Kbd_22 instance C_Kbd Ent26 Ent22 where _kbd = Kbd_26 [] kbd_ = Kbd_26 instance C_Kbd Ent28 Ent22 where _kbd = Kbd_28 [] kbd_ = Kbd_28 instance C_Kbd Ent31 Ent22 where _kbd = Kbd_31 [] kbd_ = Kbd_31 instance C_Kbd Ent33 Ent22 where _kbd = Kbd_33 [] kbd_ = Kbd_33 class C_Var a b | a -> b where _var :: [b] -> a var_ :: [Att11] -> [b] -> a instance C_Var Ent3 Ent22 where _var = Var_3 [] var_ = Var_3 instance C_Var Ent4 Ent4 where _var = Var_4 [] var_ = Var_4 instance C_Var Ent6 Ent4 where _var = Var_6 [] var_ = Var_6 instance C_Var Ent10 Ent4 where _var = Var_10 [] var_ = Var_10 instance C_Var Ent12 Ent4 where _var = Var_12 [] var_ = Var_12 instance C_Var Ent17 Ent4 where _var = Var_17 [] var_ = Var_17 instance C_Var Ent21 Ent4 where _var = Var_21 [] var_ = Var_21 instance C_Var Ent22 Ent22 where _var = Var_22 [] var_ = Var_22 instance C_Var Ent26 Ent22 where _var = Var_26 [] var_ = Var_26 instance C_Var Ent28 Ent22 where _var = Var_28 [] var_ = Var_28 instance C_Var Ent31 Ent22 where _var = Var_31 [] var_ = Var_31 instance C_Var Ent33 Ent22 where _var = Var_33 [] var_ = Var_33 class C_Cite a b | a -> b where _cite :: [b] -> a cite_ :: [Att11] -> [b] -> a instance C_Cite Ent3 Ent22 where _cite = Cite_3 [] cite_ = Cite_3 instance C_Cite Ent4 Ent4 where _cite = Cite_4 [] cite_ = Cite_4 instance C_Cite Ent6 Ent4 where _cite = Cite_6 [] cite_ = Cite_6 instance C_Cite Ent10 Ent4 where _cite = Cite_10 [] cite_ = Cite_10 instance C_Cite Ent12 Ent4 where _cite = Cite_12 [] cite_ = Cite_12 instance C_Cite Ent17 Ent4 where _cite = Cite_17 [] cite_ = Cite_17 instance C_Cite Ent21 Ent4 where _cite = Cite_21 [] cite_ = Cite_21 instance C_Cite Ent22 Ent22 where _cite = Cite_22 [] cite_ = Cite_22 instance C_Cite Ent26 Ent22 where _cite = Cite_26 [] cite_ = Cite_26 instance C_Cite Ent28 Ent22 where _cite = Cite_28 [] cite_ = Cite_28 instance C_Cite Ent31 Ent22 where _cite = Cite_31 [] cite_ = Cite_31 instance C_Cite Ent33 Ent22 where _cite = Cite_33 [] cite_ = Cite_33 class C_Abbr a b | a -> b where _abbr :: [b] -> a abbr_ :: [Att11] -> [b] -> a instance C_Abbr Ent3 Ent22 where _abbr = Abbr_3 [] abbr_ = Abbr_3 instance C_Abbr Ent4 Ent4 where _abbr = Abbr_4 [] abbr_ = Abbr_4 instance C_Abbr Ent6 Ent4 where _abbr = Abbr_6 [] abbr_ = Abbr_6 instance C_Abbr Ent10 Ent4 where _abbr = Abbr_10 [] abbr_ = Abbr_10 instance C_Abbr Ent12 Ent4 where _abbr = Abbr_12 [] abbr_ = Abbr_12 instance C_Abbr Ent17 Ent4 where _abbr = Abbr_17 [] abbr_ = Abbr_17 instance C_Abbr Ent21 Ent4 where _abbr = Abbr_21 [] abbr_ = Abbr_21 instance C_Abbr Ent22 Ent22 where _abbr = Abbr_22 [] abbr_ = Abbr_22 instance C_Abbr Ent26 Ent22 where _abbr = Abbr_26 [] abbr_ = Abbr_26 instance C_Abbr Ent28 Ent22 where _abbr = Abbr_28 [] abbr_ = Abbr_28 instance C_Abbr Ent31 Ent22 where _abbr = Abbr_31 [] abbr_ = Abbr_31 instance C_Abbr Ent33 Ent22 where _abbr = Abbr_33 [] abbr_ = Abbr_33 class C_Acronym a b | a -> b where _acronym :: [b] -> a acronym_ :: [Att11] -> [b] -> a instance C_Acronym Ent3 Ent22 where _acronym = Acronym_3 [] acronym_ = Acronym_3 instance C_Acronym Ent4 Ent4 where _acronym = Acronym_4 [] acronym_ = Acronym_4 instance C_Acronym Ent6 Ent4 where _acronym = Acronym_6 [] acronym_ = Acronym_6 instance C_Acronym Ent10 Ent4 where _acronym = Acronym_10 [] acronym_ = Acronym_10 instance C_Acronym Ent12 Ent4 where _acronym = Acronym_12 [] acronym_ = Acronym_12 instance C_Acronym Ent17 Ent4 where _acronym = Acronym_17 [] acronym_ = Acronym_17 instance C_Acronym Ent21 Ent4 where _acronym = Acronym_21 [] acronym_ = Acronym_21 instance C_Acronym Ent22 Ent22 where _acronym = Acronym_22 [] acronym_ = Acronym_22 instance C_Acronym Ent26 Ent22 where _acronym = Acronym_26 [] acronym_ = Acronym_26 instance C_Acronym Ent28 Ent22 where _acronym = Acronym_28 [] acronym_ = Acronym_28 instance C_Acronym Ent31 Ent22 where _acronym = Acronym_31 [] acronym_ = Acronym_31 instance C_Acronym Ent33 Ent22 where _acronym = Acronym_33 [] acronym_ = Acronym_33 class C_Q a b | a -> b where _q :: [b] -> a q_ :: [Att14] -> [b] -> a instance C_Q Ent3 Ent22 where _q = Q_3 [] q_ = Q_3 instance C_Q Ent4 Ent4 where _q = Q_4 [] q_ = Q_4 instance C_Q Ent6 Ent4 where _q = Q_6 [] q_ = Q_6 instance C_Q Ent10 Ent4 where _q = Q_10 [] q_ = Q_10 instance C_Q Ent12 Ent4 where _q = Q_12 [] q_ = Q_12 instance C_Q Ent17 Ent4 where _q = Q_17 [] q_ = Q_17 instance C_Q Ent21 Ent4 where _q = Q_21 [] q_ = Q_21 instance C_Q Ent22 Ent22 where _q = Q_22 [] q_ = Q_22 instance C_Q Ent26 Ent22 where _q = Q_26 [] q_ = Q_26 instance C_Q Ent28 Ent22 where _q = Q_28 [] q_ = Q_28 instance C_Q Ent31 Ent22 where _q = Q_31 [] q_ = Q_31 instance C_Q Ent33 Ent22 where _q = Q_33 [] q_ = Q_33 class C_Sub a b | a -> b where _sub :: [b] -> a sub_ :: [Att11] -> [b] -> a instance C_Sub Ent3 Ent22 where _sub = Sub_3 [] sub_ = Sub_3 instance C_Sub Ent4 Ent4 where _sub = Sub_4 [] sub_ = Sub_4 instance C_Sub Ent6 Ent4 where _sub = Sub_6 [] sub_ = Sub_6 instance C_Sub Ent10 Ent4 where _sub = Sub_10 [] sub_ = Sub_10 instance C_Sub Ent12 Ent4 where _sub = Sub_12 [] sub_ = Sub_12 instance C_Sub Ent17 Ent4 where _sub = Sub_17 [] sub_ = Sub_17 instance C_Sub Ent21 Ent4 where _sub = Sub_21 [] sub_ = Sub_21 instance C_Sub Ent22 Ent22 where _sub = Sub_22 [] sub_ = Sub_22 instance C_Sub Ent26 Ent22 where _sub = Sub_26 [] sub_ = Sub_26 instance C_Sub Ent28 Ent22 where _sub = Sub_28 [] sub_ = Sub_28 instance C_Sub Ent31 Ent22 where _sub = Sub_31 [] sub_ = Sub_31 instance C_Sub Ent33 Ent22 where _sub = Sub_33 [] sub_ = Sub_33 class C_Sup a b | a -> b where _sup :: [b] -> a sup_ :: [Att11] -> [b] -> a instance C_Sup Ent3 Ent22 where _sup = Sup_3 [] sup_ = Sup_3 instance C_Sup Ent4 Ent4 where _sup = Sup_4 [] sup_ = Sup_4 instance C_Sup Ent6 Ent4 where _sup = Sup_6 [] sup_ = Sup_6 instance C_Sup Ent10 Ent4 where _sup = Sup_10 [] sup_ = Sup_10 instance C_Sup Ent12 Ent4 where _sup = Sup_12 [] sup_ = Sup_12 instance C_Sup Ent17 Ent4 where _sup = Sup_17 [] sup_ = Sup_17 instance C_Sup Ent21 Ent4 where _sup = Sup_21 [] sup_ = Sup_21 instance C_Sup Ent22 Ent22 where _sup = Sup_22 [] sup_ = Sup_22 instance C_Sup Ent26 Ent22 where _sup = Sup_26 [] sup_ = Sup_26 instance C_Sup Ent28 Ent22 where _sup = Sup_28 [] sup_ = Sup_28 instance C_Sup Ent31 Ent22 where _sup = Sup_31 [] sup_ = Sup_31 instance C_Sup Ent33 Ent22 where _sup = Sup_33 [] sup_ = Sup_33 class C_Tt a b | a -> b where _tt :: [b] -> a tt_ :: [Att11] -> [b] -> a instance C_Tt Ent3 Ent22 where _tt = Tt_3 [] tt_ = Tt_3 instance C_Tt Ent4 Ent4 where _tt = Tt_4 [] tt_ = Tt_4 instance C_Tt Ent6 Ent4 where _tt = Tt_6 [] tt_ = Tt_6 instance C_Tt Ent10 Ent4 where _tt = Tt_10 [] tt_ = Tt_10 instance C_Tt Ent12 Ent4 where _tt = Tt_12 [] tt_ = Tt_12 instance C_Tt Ent17 Ent4 where _tt = Tt_17 [] tt_ = Tt_17 instance C_Tt Ent21 Ent4 where _tt = Tt_21 [] tt_ = Tt_21 instance C_Tt Ent22 Ent22 where _tt = Tt_22 [] tt_ = Tt_22 instance C_Tt Ent26 Ent22 where _tt = Tt_26 [] tt_ = Tt_26 instance C_Tt Ent28 Ent22 where _tt = Tt_28 [] tt_ = Tt_28 instance C_Tt Ent31 Ent22 where _tt = Tt_31 [] tt_ = Tt_31 instance C_Tt Ent33 Ent22 where _tt = Tt_33 [] tt_ = Tt_33 class C_I a b | a -> b where _i :: [b] -> a i_ :: [Att11] -> [b] -> a instance C_I Ent3 Ent22 where _i = I_3 [] i_ = I_3 instance C_I Ent4 Ent4 where _i = I_4 [] i_ = I_4 instance C_I Ent6 Ent4 where _i = I_6 [] i_ = I_6 instance C_I Ent10 Ent4 where _i = I_10 [] i_ = I_10 instance C_I Ent12 Ent4 where _i = I_12 [] i_ = I_12 instance C_I Ent17 Ent4 where _i = I_17 [] i_ = I_17 instance C_I Ent21 Ent4 where _i = I_21 [] i_ = I_21 instance C_I Ent22 Ent22 where _i = I_22 [] i_ = I_22 instance C_I Ent26 Ent22 where _i = I_26 [] i_ = I_26 instance C_I Ent28 Ent22 where _i = I_28 [] i_ = I_28 instance C_I Ent31 Ent22 where _i = I_31 [] i_ = I_31 instance C_I Ent33 Ent22 where _i = I_33 [] i_ = I_33 class C_B a b | a -> b where _b :: [b] -> a b_ :: [Att11] -> [b] -> a instance C_B Ent3 Ent22 where _b = B_3 [] b_ = B_3 instance C_B Ent4 Ent4 where _b = B_4 [] b_ = B_4 instance C_B Ent6 Ent4 where _b = B_6 [] b_ = B_6 instance C_B Ent10 Ent4 where _b = B_10 [] b_ = B_10 instance C_B Ent12 Ent4 where _b = B_12 [] b_ = B_12 instance C_B Ent17 Ent4 where _b = B_17 [] b_ = B_17 instance C_B Ent21 Ent4 where _b = B_21 [] b_ = B_21 instance C_B Ent22 Ent22 where _b = B_22 [] b_ = B_22 instance C_B Ent26 Ent22 where _b = B_26 [] b_ = B_26 instance C_B Ent28 Ent22 where _b = B_28 [] b_ = B_28 instance C_B Ent31 Ent22 where _b = B_31 [] b_ = B_31 instance C_B Ent33 Ent22 where _b = B_33 [] b_ = B_33 class C_Big a b | a -> b where _big :: [b] -> a big_ :: [Att11] -> [b] -> a instance C_Big Ent3 Ent22 where _big = Big_3 [] big_ = Big_3 instance C_Big Ent4 Ent4 where _big = Big_4 [] big_ = Big_4 instance C_Big Ent6 Ent4 where _big = Big_6 [] big_ = Big_6 instance C_Big Ent10 Ent4 where _big = Big_10 [] big_ = Big_10 instance C_Big Ent12 Ent4 where _big = Big_12 [] big_ = Big_12 instance C_Big Ent17 Ent4 where _big = Big_17 [] big_ = Big_17 instance C_Big Ent21 Ent4 where _big = Big_21 [] big_ = Big_21 instance C_Big Ent22 Ent22 where _big = Big_22 [] big_ = Big_22 instance C_Big Ent26 Ent22 where _big = Big_26 [] big_ = Big_26 instance C_Big Ent28 Ent22 where _big = Big_28 [] big_ = Big_28 instance C_Big Ent31 Ent22 where _big = Big_31 [] big_ = Big_31 instance C_Big Ent33 Ent22 where _big = Big_33 [] big_ = Big_33 class C_Small a b | a -> b where _small :: [b] -> a small_ :: [Att11] -> [b] -> a instance C_Small Ent3 Ent22 where _small = Small_3 [] small_ = Small_3 instance C_Small Ent4 Ent4 where _small = Small_4 [] small_ = Small_4 instance C_Small Ent6 Ent4 where _small = Small_6 [] small_ = Small_6 instance C_Small Ent10 Ent4 where _small = Small_10 [] small_ = Small_10 instance C_Small Ent12 Ent4 where _small = Small_12 [] small_ = Small_12 instance C_Small Ent17 Ent4 where _small = Small_17 [] small_ = Small_17 instance C_Small Ent21 Ent4 where _small = Small_21 [] small_ = Small_21 instance C_Small Ent22 Ent22 where _small = Small_22 [] small_ = Small_22 instance C_Small Ent26 Ent22 where _small = Small_26 [] small_ = Small_26 instance C_Small Ent28 Ent22 where _small = Small_28 [] small_ = Small_28 instance C_Small Ent31 Ent22 where _small = Small_31 [] small_ = Small_31 instance C_Small Ent33 Ent22 where _small = Small_33 [] small_ = Small_33 class C_Object a b | a -> b where _object :: [b] -> a object_ :: [Att20] -> [b] -> a instance C_Object Ent1 Ent3 where _object = Object_1 [] object_ = Object_1 instance C_Object Ent3 Ent3 where _object = Object_3 [] object_ = Object_3 instance C_Object Ent4 Ent17 where _object = Object_4 [] object_ = Object_4 instance C_Object Ent6 Ent17 where _object = Object_6 [] object_ = Object_6 instance C_Object Ent12 Ent17 where _object = Object_12 [] object_ = Object_12 instance C_Object Ent17 Ent17 where _object = Object_17 [] object_ = Object_17 instance C_Object Ent21 Ent17 where _object = Object_21 [] object_ = Object_21 instance C_Object Ent22 Ent3 where _object = Object_22 [] object_ = Object_22 instance C_Object Ent26 Ent3 where _object = Object_26 [] object_ = Object_26 instance C_Object Ent28 Ent3 where _object = Object_28 [] object_ = Object_28 instance C_Object Ent33 Ent3 where _object = Object_33 [] object_ = Object_33 class C_Param a where _param :: a param_ :: [Att21] -> a instance C_Param Ent3 where _param = Param_3 [] param_ = Param_3 instance C_Param Ent17 where _param = Param_17 [] param_ = Param_17 class C_Img a where _img :: a img_ :: [Att22] -> a instance C_Img Ent3 where _img = Img_3 [] img_ = Img_3 instance C_Img Ent4 where _img = Img_4 [] img_ = Img_4 instance C_Img Ent6 where _img = Img_6 [] img_ = Img_6 instance C_Img Ent12 where _img = Img_12 [] img_ = Img_12 instance C_Img Ent17 where _img = Img_17 [] img_ = Img_17 instance C_Img Ent21 where _img = Img_21 [] img_ = Img_21 instance C_Img Ent22 where _img = Img_22 [] img_ = Img_22 instance C_Img Ent26 where _img = Img_26 [] img_ = Img_26 instance C_Img Ent28 where _img = Img_28 [] img_ = Img_28 instance C_Img Ent33 where _img = Img_33 [] img_ = Img_33 class C_Map a b | a -> b where _map :: [b] -> a map_ :: [Att25] -> [b] -> a instance C_Map Ent3 Ent23 where _map = Map_3 [] map_ = Map_3 instance C_Map Ent4 Ent18 where _map = Map_4 [] map_ = Map_4 instance C_Map Ent6 Ent18 where _map = Map_6 [] map_ = Map_6 instance C_Map Ent10 Ent18 where _map = Map_10 [] map_ = Map_10 instance C_Map Ent12 Ent18 where _map = Map_12 [] map_ = Map_12 instance C_Map Ent17 Ent18 where _map = Map_17 [] map_ = Map_17 instance C_Map Ent21 Ent18 where _map = Map_21 [] map_ = Map_21 instance C_Map Ent22 Ent23 where _map = Map_22 [] map_ = Map_22 instance C_Map Ent26 Ent23 where _map = Map_26 [] map_ = Map_26 instance C_Map Ent28 Ent23 where _map = Map_28 [] map_ = Map_28 instance C_Map Ent31 Ent23 where _map = Map_31 [] map_ = Map_31 instance C_Map Ent33 Ent23 where _map = Map_33 [] map_ = Map_33 class C_Area a where _area :: a area_ :: [Att27] -> a instance C_Area Ent18 where _area = Area_18 [] area_ = Area_18 instance C_Area Ent23 where _area = Area_23 [] area_ = Area_23 class C_Form a b | a -> b where _form :: [b] -> a form_ :: [Att28] -> [b] -> a instance C_Form Ent3 Ent32 where _form = Form_3 [] form_ = Form_3 instance C_Form Ent6 Ent11 where _form = Form_6 [] form_ = Form_6 instance C_Form Ent7 Ent11 where _form = Form_7 [] form_ = Form_7 instance C_Form Ent12 Ent11 where _form = Form_12 [] form_ = Form_12 instance C_Form Ent17 Ent11 where _form = Form_17 [] form_ = Form_17 instance C_Form Ent18 Ent11 where _form = Form_18 [] form_ = Form_18 instance C_Form Ent23 Ent32 where _form = Form_23 [] form_ = Form_23 instance C_Form Ent27 Ent32 where _form = Form_27 [] form_ = Form_27 instance C_Form Ent28 Ent32 where _form = Form_28 [] form_ = Form_28 instance C_Form Ent33 Ent32 where _form = Form_33 [] form_ = Form_33 class C_Label a b | a -> b where _label :: [b] -> a label_ :: [Att30] -> [b] -> a instance C_Label Ent3 Ent22 where _label = Label_3 [] label_ = Label_3 instance C_Label Ent4 Ent4 where _label = Label_4 [] label_ = Label_4 instance C_Label Ent6 Ent4 where _label = Label_6 [] label_ = Label_6 instance C_Label Ent10 Ent4 where _label = Label_10 [] label_ = Label_10 instance C_Label Ent12 Ent4 where _label = Label_12 [] label_ = Label_12 instance C_Label Ent17 Ent4 where _label = Label_17 [] label_ = Label_17 instance C_Label Ent22 Ent22 where _label = Label_22 [] label_ = Label_22 instance C_Label Ent28 Ent22 where _label = Label_28 [] label_ = Label_28 instance C_Label Ent31 Ent22 where _label = Label_31 [] label_ = Label_31 instance C_Label Ent33 Ent22 where _label = Label_33 [] label_ = Label_33 class C_Input a where _input :: a input_ :: [Att31] -> a instance C_Input Ent3 where _input = Input_3 [] input_ = Input_3 instance C_Input Ent4 where _input = Input_4 [] input_ = Input_4 instance C_Input Ent6 where _input = Input_6 [] input_ = Input_6 instance C_Input Ent10 where _input = Input_10 [] input_ = Input_10 instance C_Input Ent12 where _input = Input_12 [] input_ = Input_12 instance C_Input Ent17 where _input = Input_17 [] input_ = Input_17 instance C_Input Ent22 where _input = Input_22 [] input_ = Input_22 instance C_Input Ent28 where _input = Input_28 [] input_ = Input_28 instance C_Input Ent31 where _input = Input_31 [] input_ = Input_31 instance C_Input Ent33 where _input = Input_33 [] input_ = Input_33 class C_Select a b | a -> b where _select :: [b] -> a select_ :: [Att32] -> [b] -> a instance C_Select Ent3 Ent24 where _select = Select_3 [] select_ = Select_3 instance C_Select Ent4 Ent19 where _select = Select_4 [] select_ = Select_4 instance C_Select Ent6 Ent19 where _select = Select_6 [] select_ = Select_6 instance C_Select Ent10 Ent19 where _select = Select_10 [] select_ = Select_10 instance C_Select Ent12 Ent19 where _select = Select_12 [] select_ = Select_12 instance C_Select Ent17 Ent19 where _select = Select_17 [] select_ = Select_17 instance C_Select Ent22 Ent24 where _select = Select_22 [] select_ = Select_22 instance C_Select Ent28 Ent24 where _select = Select_28 [] select_ = Select_28 instance C_Select Ent31 Ent24 where _select = Select_31 [] select_ = Select_31 instance C_Select Ent33 Ent24 where _select = Select_33 [] select_ = Select_33 class C_Optgroup a b | a -> b where _optgroup :: [b] -> a optgroup_ :: [Att33] -> [b] -> a instance C_Optgroup Ent19 Ent20 where _optgroup = Optgroup_19 [] optgroup_ = Optgroup_19 instance C_Optgroup Ent24 Ent25 where _optgroup = Optgroup_24 [] optgroup_ = Optgroup_24 class C_Option a b | a -> b where _option :: [b] -> a option_ :: [Att35] -> [b] -> a instance C_Option Ent19 Ent5 where _option = Option_19 [] option_ = Option_19 instance C_Option Ent20 Ent5 where _option = Option_20 [] option_ = Option_20 instance C_Option Ent24 Ent2 where _option = Option_24 [] option_ = Option_24 instance C_Option Ent25 Ent2 where _option = Option_25 [] option_ = Option_25 class C_Textarea a b | a -> b where _textarea :: [b] -> a textarea_ :: [Att36] -> [b] -> a instance C_Textarea Ent3 Ent2 where _textarea = Textarea_3 [] textarea_ = Textarea_3 instance C_Textarea Ent4 Ent5 where _textarea = Textarea_4 [] textarea_ = Textarea_4 instance C_Textarea Ent6 Ent5 where _textarea = Textarea_6 [] textarea_ = Textarea_6 instance C_Textarea Ent10 Ent5 where _textarea = Textarea_10 [] textarea_ = Textarea_10 instance C_Textarea Ent12 Ent5 where _textarea = Textarea_12 [] textarea_ = Textarea_12 instance C_Textarea Ent17 Ent5 where _textarea = Textarea_17 [] textarea_ = Textarea_17 instance C_Textarea Ent22 Ent2 where _textarea = Textarea_22 [] textarea_ = Textarea_22 instance C_Textarea Ent28 Ent2 where _textarea = Textarea_28 [] textarea_ = Textarea_28 instance C_Textarea Ent31 Ent2 where _textarea = Textarea_31 [] textarea_ = Textarea_31 instance C_Textarea Ent33 Ent2 where _textarea = Textarea_33 [] textarea_ = Textarea_33 class C_Fieldset a b | a -> b where _fieldset :: [b] -> a fieldset_ :: [Att11] -> [b] -> a instance C_Fieldset Ent3 Ent33 where _fieldset = Fieldset_3 [] fieldset_ = Fieldset_3 instance C_Fieldset Ent6 Ent12 where _fieldset = Fieldset_6 [] fieldset_ = Fieldset_6 instance C_Fieldset Ent7 Ent12 where _fieldset = Fieldset_7 [] fieldset_ = Fieldset_7 instance C_Fieldset Ent11 Ent12 where _fieldset = Fieldset_11 [] fieldset_ = Fieldset_11 instance C_Fieldset Ent12 Ent12 where _fieldset = Fieldset_12 [] fieldset_ = Fieldset_12 instance C_Fieldset Ent17 Ent12 where _fieldset = Fieldset_17 [] fieldset_ = Fieldset_17 instance C_Fieldset Ent18 Ent12 where _fieldset = Fieldset_18 [] fieldset_ = Fieldset_18 instance C_Fieldset Ent23 Ent33 where _fieldset = Fieldset_23 [] fieldset_ = Fieldset_23 instance C_Fieldset Ent27 Ent33 where _fieldset = Fieldset_27 [] fieldset_ = Fieldset_27 instance C_Fieldset Ent28 Ent33 where _fieldset = Fieldset_28 [] fieldset_ = Fieldset_28 instance C_Fieldset Ent32 Ent33 where _fieldset = Fieldset_32 [] fieldset_ = Fieldset_32 instance C_Fieldset Ent33 Ent33 where _fieldset = Fieldset_33 [] fieldset_ = Fieldset_33 class C_Legend a b | a -> b where _legend :: [b] -> a legend_ :: [Att39] -> [b] -> a instance C_Legend Ent12 Ent4 where _legend = Legend_12 [] legend_ = Legend_12 instance C_Legend Ent33 Ent22 where _legend = Legend_33 [] legend_ = Legend_33 class C_Button a b | a -> b where _button :: [b] -> a button_ :: [Att40] -> [b] -> a instance C_Button Ent3 Ent26 where _button = Button_3 [] button_ = Button_3 instance C_Button Ent4 Ent21 where _button = Button_4 [] button_ = Button_4 instance C_Button Ent6 Ent21 where _button = Button_6 [] button_ = Button_6 instance C_Button Ent10 Ent21 where _button = Button_10 [] button_ = Button_10 instance C_Button Ent12 Ent21 where _button = Button_12 [] button_ = Button_12 instance C_Button Ent17 Ent21 where _button = Button_17 [] button_ = Button_17 instance C_Button Ent22 Ent26 where _button = Button_22 [] button_ = Button_22 instance C_Button Ent28 Ent26 where _button = Button_28 [] button_ = Button_28 instance C_Button Ent31 Ent26 where _button = Button_31 [] button_ = Button_31 instance C_Button Ent33 Ent26 where _button = Button_33 [] button_ = Button_33 class C_Table a b | a -> b where _table :: [b] -> a table_ :: [Att41] -> [b] -> a instance C_Table Ent3 Ent34 where _table = Table_3 [] table_ = Table_3 instance C_Table Ent6 Ent13 where _table = Table_6 [] table_ = Table_6 instance C_Table Ent7 Ent13 where _table = Table_7 [] table_ = Table_7 instance C_Table Ent11 Ent13 where _table = Table_11 [] table_ = Table_11 instance C_Table Ent12 Ent13 where _table = Table_12 [] table_ = Table_12 instance C_Table Ent17 Ent13 where _table = Table_17 [] table_ = Table_17 instance C_Table Ent18 Ent13 where _table = Table_18 [] table_ = Table_18 instance C_Table Ent21 Ent13 where _table = Table_21 [] table_ = Table_21 instance C_Table Ent23 Ent34 where _table = Table_23 [] table_ = Table_23 instance C_Table Ent26 Ent34 where _table = Table_26 [] table_ = Table_26 instance C_Table Ent27 Ent34 where _table = Table_27 [] table_ = Table_27 instance C_Table Ent28 Ent34 where _table = Table_28 [] table_ = Table_28 instance C_Table Ent32 Ent34 where _table = Table_32 [] table_ = Table_32 instance C_Table Ent33 Ent34 where _table = Table_33 [] table_ = Table_33 class C_Caption a b | a -> b where _caption :: [b] -> a caption_ :: [Att11] -> [b] -> a instance C_Caption Ent13 Ent4 where _caption = Caption_13 [] caption_ = Caption_13 instance C_Caption Ent34 Ent22 where _caption = Caption_34 [] caption_ = Caption_34 class C_Thead a b | a -> b where _thead :: [b] -> a thead_ :: [Att42] -> [b] -> a instance C_Thead Ent13 Ent14 where _thead = Thead_13 [] thead_ = Thead_13 instance C_Thead Ent34 Ent35 where _thead = Thead_34 [] thead_ = Thead_34 class C_Tfoot a b | a -> b where _tfoot :: [b] -> a tfoot_ :: [Att42] -> [b] -> a instance C_Tfoot Ent13 Ent14 where _tfoot = Tfoot_13 [] tfoot_ = Tfoot_13 instance C_Tfoot Ent34 Ent35 where _tfoot = Tfoot_34 [] tfoot_ = Tfoot_34 class C_Tbody a b | a -> b where _tbody :: [b] -> a tbody_ :: [Att42] -> [b] -> a instance C_Tbody Ent13 Ent14 where _tbody = Tbody_13 [] tbody_ = Tbody_13 instance C_Tbody Ent34 Ent35 where _tbody = Tbody_34 [] tbody_ = Tbody_34 class C_Colgroup a b | a -> b where _colgroup :: [b] -> a colgroup_ :: [Att43] -> [b] -> a instance C_Colgroup Ent13 Ent14 where _colgroup = Colgroup_13 [] colgroup_ = Colgroup_13 instance C_Colgroup Ent34 Ent35 where _colgroup = Colgroup_34 [] colgroup_ = Colgroup_34 class C_Col a where _col :: a col_ :: [Att43] -> a instance C_Col Ent13 where _col = Col_13 [] col_ = Col_13 instance C_Col Ent15 where _col = Col_15 [] col_ = Col_15 instance C_Col Ent34 where _col = Col_34 [] col_ = Col_34 instance C_Col Ent36 where _col = Col_36 [] col_ = Col_36 class C_Tr a b | a -> b where _tr :: [b] -> a tr_ :: [Att42] -> [b] -> a instance C_Tr Ent13 Ent16 where _tr = Tr_13 [] tr_ = Tr_13 instance C_Tr Ent14 Ent16 where _tr = Tr_14 [] tr_ = Tr_14 instance C_Tr Ent34 Ent37 where _tr = Tr_34 [] tr_ = Tr_34 instance C_Tr Ent35 Ent37 where _tr = Tr_35 [] tr_ = Tr_35 class C_Th a b | a -> b where _th :: [b] -> a th_ :: [Att44] -> [b] -> a instance C_Th Ent16 Ent6 where _th = Th_16 [] th_ = Th_16 instance C_Th Ent37 Ent28 where _th = Th_37 [] th_ = Th_37 class C_Td a b | a -> b where _td :: [b] -> a td_ :: [Att44] -> [b] -> a instance C_Td Ent16 Ent6 where _td = Td_16 [] td_ = Td_16 instance C_Td Ent37 Ent28 where _td = Td_37 [] td_ = Td_37 class C_PCDATA a where pcdata :: String -> a pcdata_bs :: B.ByteString -> a instance C_PCDATA Ent2 where pcdata s = PCDATA_2 [] (s2b_escape s) pcdata_bs = PCDATA_2 [] instance C_PCDATA Ent3 where pcdata s = PCDATA_3 [] (s2b_escape s) pcdata_bs = PCDATA_3 [] instance C_PCDATA Ent4 where pcdata s = PCDATA_4 [] (s2b_escape s) pcdata_bs = PCDATA_4 [] instance C_PCDATA Ent5 where pcdata s = PCDATA_5 [] (s2b_escape s) pcdata_bs = PCDATA_5 [] instance C_PCDATA Ent6 where pcdata s = PCDATA_6 [] (s2b_escape s) pcdata_bs = PCDATA_6 [] instance C_PCDATA Ent10 where pcdata s = PCDATA_10 [] (s2b_escape s) pcdata_bs = PCDATA_10 [] instance C_PCDATA Ent12 where pcdata s = PCDATA_12 [] (s2b_escape s) pcdata_bs = PCDATA_12 [] instance C_PCDATA Ent17 where pcdata s = PCDATA_17 [] (s2b_escape s) pcdata_bs = PCDATA_17 [] instance C_PCDATA Ent21 where pcdata s = PCDATA_21 [] (s2b_escape s) pcdata_bs = PCDATA_21 [] instance C_PCDATA Ent22 where pcdata s = PCDATA_22 [] (s2b_escape s) pcdata_bs = PCDATA_22 [] instance C_PCDATA Ent26 where pcdata s = PCDATA_26 [] (s2b_escape s) pcdata_bs = PCDATA_26 [] instance C_PCDATA Ent28 where pcdata s = PCDATA_28 [] (s2b_escape s) pcdata_bs = PCDATA_28 [] instance C_PCDATA Ent31 where pcdata s = PCDATA_31 [] (s2b_escape s) pcdata_bs = PCDATA_31 [] instance C_PCDATA Ent33 where pcdata s = PCDATA_33 [] (s2b_escape s) pcdata_bs = PCDATA_33 [] maprender a = B.concat (map render_bs a) render :: Render a => a -> String render a = U.toString (render_bs a) class Render a where render_bs :: a -> B.ByteString instance Render Ent where render_bs (Html att c) = B.concat [s2b "\n\n", s2b ""] instance Render Ent0 where render_bs (Head_0 att c) = B.concat [head_byte_b,renderAtts att,gt_byte, maprender c,head_byte_e] render_bs (Body_0 att c) = B.concat [body_byte_b,renderAtts att,gt_byte, maprender c,body_byte_e] instance Render Ent1 where render_bs (Title_1 att c) = B.concat [title_byte_b,renderAtts att,gt_byte, maprender c,title_byte_e] render_bs (Base_1 att) = B.concat [base_byte_b,renderAtts att,gts_byte] render_bs (Meta_1 att) = B.concat [meta_byte_b,renderAtts att,gts_byte] render_bs (Link_1 att) = B.concat [link_byte_b,renderAtts att,gts_byte] render_bs (Style_1 att c) = B.concat [style_byte_b,renderAtts att,gt_byte, maprender c,style_byte_e] render_bs (Script_1 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Object_1 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] instance Render Ent2 where render_bs (PCDATA_2 _ str) = str instance Render Ent3 where render_bs (Script_3 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_3 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_3 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_3 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_3 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_3 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_3 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_3 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_3 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_3 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_3 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_3 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_3 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_3 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_3 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_3 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_3 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_3 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_3 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_3 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_3 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_3 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_3 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_3 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_3 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_3 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_3 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_3 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_3 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_3 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_3 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_3 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_3 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_3 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_3 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_3 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_3 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_3 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_3 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_3 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_3 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_3 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_3 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_3 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_3 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_3 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_3 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_3 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_3 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_3 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_3 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_3 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_3 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_3 _ str) = str instance Render Ent4 where render_bs (Script_4 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_4 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_4 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_4 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_4 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_4 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_4 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_4 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_4 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_4 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_4 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_4 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_4 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_4 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_4 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_4 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_4 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_4 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_4 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_4 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_4 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_4 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_4 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_4 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_4 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_4 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_4 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_4 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_4 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_4 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_4 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_4 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_4 _ str) = str instance Render Ent5 where render_bs (PCDATA_5 _ str) = str instance Render Ent6 where render_bs (Script_6 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_6 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_6 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_6 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_6 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_6 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_6 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_6 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_6 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_6 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_6 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_6 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_6 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_6 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_6 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_6 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_6 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_6 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_6 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_6 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_6 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_6 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_6 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_6 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_6 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_6 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_6 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_6 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_6 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_6 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_6 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_6 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_6 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_6 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_6 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_6 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_6 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_6 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_6 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_6 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_6 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_6 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_6 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_6 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_6 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_6 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_6 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_6 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_6 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_6 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_6 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_6 _ str) = str instance Render Ent7 where render_bs (Script_7 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_7 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_7 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_7 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_7 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_7 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_7 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_7 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_7 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_7 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_7 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_7 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_7 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_7 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_7 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_7 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_7 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_7 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_7 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Form_7 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_7 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_7 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent8 where render_bs (Li_8 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e] instance Render Ent9 where render_bs (Dt_9 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e] render_bs (Dd_9 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e] instance Render Ent10 where render_bs (Script_10 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_10 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_10 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_10 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_10 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_10 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_10 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_10 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_10 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_10 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_10 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_10 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_10 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_10 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_10 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_10 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_10 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_10 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_10 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_10 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_10 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_10 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_10 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_10 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Map_10 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_10 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_10 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_10 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_10 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_10 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_10 _ str) = str instance Render Ent11 where render_bs (Script_11 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_11 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_11 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_11 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_11 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_11 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_11 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_11 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_11 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_11 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_11 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_11 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_11 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_11 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_11 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_11 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_11 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_11 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_11 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Fieldset_11 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_11 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent12 where render_bs (Script_12 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_12 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_12 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_12 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_12 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_12 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_12 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_12 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_12 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_12 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_12 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_12 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_12 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_12 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_12 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_12 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_12 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_12 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_12 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_12 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_12 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_12 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_12 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_12 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_12 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_12 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_12 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_12 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_12 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_12 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_12 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_12 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_12 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_12 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_12 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_12 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_12 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_12 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_12 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_12 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_12 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_12 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_12 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_12 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_12 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_12 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_12 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_12 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_12 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_12 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_12 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_12 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_12 _ str) = str instance Render Ent13 where render_bs (Caption_13 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e] render_bs (Thead_13 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e] render_bs (Tfoot_13 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e] render_bs (Tbody_13 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e] render_bs (Colgroup_13 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e] render_bs (Col_13 att) = B.concat [col_byte_b,renderAtts att,gts_byte] render_bs (Tr_13 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e] instance Render Ent14 where render_bs (Tr_14 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e] instance Render Ent15 where render_bs (Col_15 att) = B.concat [col_byte_b,renderAtts att,gts_byte] instance Render Ent16 where render_bs (Th_16 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e] render_bs (Td_16 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e] instance Render Ent17 where render_bs (Script_17 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_17 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_17 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_17 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_17 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_17 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_17 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_17 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_17 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_17 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_17 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_17 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_17 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_17 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_17 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_17 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_17 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_17 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_17 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_17 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_17 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_17 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_17 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_17 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_17 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_17 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_17 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_17 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_17 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_17 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_17 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_17 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_17 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_17 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_17 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_17 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_17 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_17 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_17 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_17 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_17 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_17 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_17 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_17 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_17 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_17 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_17 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_17 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_17 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_17 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_17 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_17 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_17 _ str) = str instance Render Ent18 where render_bs (Script_18 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_18 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_18 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_18 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_18 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_18 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_18 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_18 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_18 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_18 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_18 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_18 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_18 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_18 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_18 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_18 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_18 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_18 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_18 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Area_18 att) = B.concat [area_byte_b,renderAtts att,gts_byte] render_bs (Form_18 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_18 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_18 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent19 where render_bs (Optgroup_19 att c) = B.concat [optgroup_byte_b,renderAtts att,gt_byte, maprender c,optgroup_byte_e] render_bs (Option_19 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent20 where render_bs (Option_20 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent21 where render_bs (Script_21 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_21 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_21 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_21 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_21 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_21 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_21 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_21 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_21 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_21 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_21 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_21 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_21 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_21 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_21 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_21 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_21 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_21 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_21 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_21 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_21 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_21 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_21 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_21 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_21 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_21 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_21 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_21 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_21 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_21 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_21 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_21 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_21 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_21 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_21 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_21 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_21 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_21 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_21 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_21 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_21 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_21 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_21 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Table_21 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_21 _ str) = str instance Render Ent22 where render_bs (Script_22 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_22 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_22 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_22 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_22 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_22 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_22 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_22 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_22 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_22 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_22 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_22 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_22 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_22 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_22 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_22 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_22 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_22 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_22 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_22 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_22 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_22 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_22 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_22 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_22 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_22 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_22 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_22 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_22 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_22 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_22 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_22 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_22 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_22 _ str) = str instance Render Ent23 where render_bs (Script_23 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_23 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_23 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_23 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_23 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_23 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_23 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_23 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_23 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_23 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_23 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_23 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_23 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_23 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_23 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_23 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_23 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_23 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_23 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Area_23 att) = B.concat [area_byte_b,renderAtts att,gts_byte] render_bs (Form_23 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_23 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_23 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent24 where render_bs (Optgroup_24 att c) = B.concat [optgroup_byte_b,renderAtts att,gt_byte, maprender c,optgroup_byte_e] render_bs (Option_24 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent25 where render_bs (Option_25 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent26 where render_bs (Script_26 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_26 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_26 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_26 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_26 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_26 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_26 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_26 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_26 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_26 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_26 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_26 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_26 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_26 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_26 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_26 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_26 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_26 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_26 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_26 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_26 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_26 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_26 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_26 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_26 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_26 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_26 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_26 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_26 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_26 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_26 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_26 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_26 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_26 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_26 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_26 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_26 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_26 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_26 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_26 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_26 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_26 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_26 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Table_26 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_26 _ str) = str instance Render Ent27 where render_bs (Script_27 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_27 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_27 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_27 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_27 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_27 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_27 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_27 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_27 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_27 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_27 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_27 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_27 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_27 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_27 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_27 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_27 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_27 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_27 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Form_27 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_27 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_27 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent28 where render_bs (Script_28 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_28 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_28 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_28 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_28 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_28 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_28 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_28 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_28 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_28 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_28 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_28 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_28 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_28 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_28 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_28 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_28 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_28 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_28 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_28 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_28 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_28 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_28 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_28 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_28 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_28 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_28 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_28 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_28 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_28 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_28 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_28 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_28 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_28 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_28 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_28 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_28 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_28 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_28 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_28 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_28 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_28 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_28 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_28 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_28 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_28 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_28 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_28 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_28 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_28 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_28 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_28 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_28 _ str) = str instance Render Ent29 where render_bs (Li_29 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e] instance Render Ent30 where render_bs (Dt_30 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e] render_bs (Dd_30 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e] instance Render Ent31 where render_bs (Script_31 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_31 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_31 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_31 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_31 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_31 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_31 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_31 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_31 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_31 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_31 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_31 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_31 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_31 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_31 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_31 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_31 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_31 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_31 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_31 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_31 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_31 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_31 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_31 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_31 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Map_31 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_31 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_31 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_31 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_31 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_31 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_31 _ str) = str instance Render Ent32 where render_bs (Script_32 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_32 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_32 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_32 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_32 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_32 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_32 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_32 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_32 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_32 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_32 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_32 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_32 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_32 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_32 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_32 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_32 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_32 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_32 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Fieldset_32 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_32 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent33 where render_bs (Script_33 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_33 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_33 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_33 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_33 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_33 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_33 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_33 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_33 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_33 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_33 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_33 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_33 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_33 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_33 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_33 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_33 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_33 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_33 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_33 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_33 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_33 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_33 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_33 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_33 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_33 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_33 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_33 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_33 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_33 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_33 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_33 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_33 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_33 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_33 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_33 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_33 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_33 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_33 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_33 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_33 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_33 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_33 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_33 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_33 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_33 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_33 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_33 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_33 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_33 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_33 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_33 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_33 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_33 _ str) = str instance Render Ent34 where render_bs (Caption_34 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e] render_bs (Thead_34 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e] render_bs (Tfoot_34 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e] render_bs (Tbody_34 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e] render_bs (Colgroup_34 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e] render_bs (Col_34 att) = B.concat [col_byte_b,renderAtts att,gts_byte] render_bs (Tr_34 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e] instance Render Ent35 where render_bs (Tr_35 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e] instance Render Ent36 where render_bs (Col_36 att) = B.concat [col_byte_b,renderAtts att,gts_byte] instance Render Ent37 where render_bs (Th_37 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e] render_bs (Td_37 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e] none_byte_b = s2b "\n" cdata_byte_b = s2b "\n" pcdata_byte_b = s2b "\n" td_byte_b = s2b "\n" th_byte_b = s2b "\n" tr_byte_b = s2b "\n" col_byte_b = s2b "\n" colgroup_byte_b = s2b "\n" tbody_byte_b = s2b "\n" tfoot_byte_b = s2b "\n" thead_byte_b = s2b "\n" caption_byte_b = s2b "\n" table_byte_b = s2b "\n" button_byte_b = s2b "\n" legend_byte_b = s2b "\n" fieldset_byte_b = s2b "\n" textarea_byte_b = s2b "\n" option_byte_b = s2b "\n" optgroup_byte_b = s2b "\n" select_byte_b = s2b "\n" input_byte_b = s2b "\n" label_byte_b = s2b "\n" form_byte_b = s2b "\n" area_byte_b = s2b "\n" map_byte_b = s2b "\n" img_byte_b = s2b "\n" param_byte_b = s2b "\n" object_byte_b = s2b "\n" small_byte_b = s2b "\n" big_byte_b = s2b "\n" b_byte_b = s2b "\n" i_byte_b = s2b "\n" tt_byte_b = s2b "\n" sup_byte_b = s2b "\n" sub_byte_b = s2b "\n" q_byte_b = s2b "\n" acronym_byte_b = s2b "\n" abbr_byte_b = s2b "\n" cite_byte_b = s2b "\n" var_byte_b = s2b "\n" kbd_byte_b = s2b "\n" samp_byte_b = s2b "\n" code_byte_b = s2b "\n" dfn_byte_b = s2b "\n" strong_byte_b = s2b "\n" em_byte_b = s2b "\n" br_byte_b = s2b "\n" bdo_byte_b = s2b "\n" span_byte_b = s2b "\n" a_byte_b = s2b "\n" del_byte_b = s2b "\n" ins_byte_b = s2b "\n" blockquote_byte_b = s2b "\n" pre_byte_b = s2b "\n" hr_byte_b = s2b "\n" address_byte_b = s2b "\n" dd_byte_b = s2b "\n" dt_byte_b = s2b "\n" dl_byte_b = s2b "\n" li_byte_b = s2b "\n" ol_byte_b = s2b "\n" ul_byte_b = s2b "\n" h6_byte_b = s2b "\n" h5_byte_b = s2b "\n" h4_byte_b = s2b "\n" h3_byte_b = s2b "\n" h2_byte_b = s2b "\n" h1_byte_b = s2b "\n" p_byte_b = s2b "\n" div_byte_b = s2b "\n" body_byte_b = s2b "\n" noscript_byte_b = s2b "\n" script_byte_b = s2b "\n" style_byte_b = s2b "\n" link_byte_b = s2b "\n" meta_byte_b = s2b "\n" base_byte_b = s2b "\n" title_byte_b = s2b "\n" head_byte_b = s2b "\n" html_byte_b = s2b "\n" http_equiv_byte = s2b "http-equiv" content_byte = s2b "content" nohref_byte = s2b "nohref" onkeydown_byte = s2b "onkeydown" onkeyup_byte = s2b "onkeyup" onreset_byte = s2b "onreset" onmouseup_byte = s2b "onmouseup" tex_byte = s2b "tex" scope_byte = s2b "scope" onmouseover_byte = s2b "onmouseover" align_byte = s2b "align" lang_byte = s2b "lang" valign_byte = s2b "valign" name_byte = s2b "name" charset_byte = s2b "charset" scheme_byte = s2b "scheme" accept_charset_byte = s2b "accept-charset" onmousedown_byte = s2b "onmousedown" rev_byte = s2b "rev" span_byte = s2b "span" title_byte = s2b "title" onclick_byte = s2b "onclick" ge_byte = s2b "ge" width_byte = s2b "width" enctype_byte = s2b "enctype" ismap_byte = s2b "ismap" usemap_byte = s2b "usemap" coords_byte = s2b "coords" frame_byte = s2b "frame" size_byte = s2b "size" onblur_byte = s2b "onblur" datetime_byte = s2b "datetime" dir_byte = s2b "dir" summary_byte = s2b "summary" method_byte = s2b "method" x_www_form_urlencode_byte = s2b "x-www-form-urlencode" standby_byte = s2b "standby" tabindex_byte = s2b "tabindex" style_byte = s2b "style" onmousemove_byte = s2b "onmousemove" height_byte = s2b "height" codetype_byte = s2b "codetype" char_byte = s2b "char" multiple_byte = s2b "multiple" codebase_byte = s2b "codebase" xmlns_byte = s2b "xmlns" profile_byte = s2b "profile" rel_byte = s2b "rel" onsubmit_byte = s2b "onsubmit" ondblclick_byte = s2b "ondblclick" axis_byte = s2b "axis" cols_byte = s2b "cols" abbr_byte = s2b "abbr" onchange_byte = s2b "onchange" readonly_byte = s2b "readonly" href_byte = s2b "href" media_byte = s2b "media" id_byte = s2b "id" for_byte = s2b "for" src_byte = s2b "src" value_byte = s2b "value" data_byte = s2b "data" hreflang_byte = s2b "hreflang" checked_byte = s2b "checked" declare_byte = s2b "declare" onkeypress_byte = s2b "onkeypress" label_byte = s2b "label" class_byte = s2b "class" type_byte = s2b "type" shape_byte = s2b "shape" accesskey_byte = s2b "accesskey" headers_byte = s2b "headers" disabled_byte = s2b "disabled" rules_byte = s2b "rules" rows_byte = s2b "rows" onfocus_byte = s2b "onfocus" colspan_byte = s2b "colspan" rowspan_byte = s2b "rowspan" defer_byte = s2b "defer" dat_byte = s2b "dat" cellspacing_byte = s2b "cellspacing" charoff_byte = s2b "charoff" cite_byte = s2b "cite" maxlength_byte = s2b "maxlength" onselect_byte = s2b "onselect" accept_byte = s2b "accept" archive_byte = s2b "archive" alt_byte = s2b "alt" rec_byte = s2b "rec" classid_byte = s2b "classid" longdesc_byte = s2b "longdesc" onmouseout_byte = s2b "onmouseout" space_byte = s2b "space" border_byte = s2b "border" onunload_byte = s2b "onunload" submi_byte = s2b "submi" onload_byte = s2b "onload" action_byte = s2b "action" cellpadding_byte = s2b "cellpadding" valuetype_byte = s2b "valuetype" selected_byte = s2b "selected" tagList = [("html",0),("head",1),("title",2),("base",3),("meta",5),("link",7),("style",8),("script",10),("noscript",11),("body",12),("div",11),("p",11),("h1",11),("h2",11),("h3",11),("h4",11),("h5",11),("h6",11),("ul",11),("ol",11),("li",11),("dl",11),("dt",11),("dd",11),("address",11),("hr",11),("pre",13),("blockquote",14),("ins",15),("del",15),("a",16),("span",11),("bdo",11),("br",19),("em",11),("strong",11),("dfn",11),("code",11),("samp",11),("kbd",11),("var",11),("cite",11),("abbr",11),("acronym",11),("q",14),("sub",11),("sup",11),("tt",11),("i",11),("b",11),("big",11),("small",11),("object",20),("param",21),("img",22),("map",25),("area",27),("form",28),("label",30),("input",31),("select",32),("optgroup",33),("option",35),("textarea",36),("fieldset",11),("legend",39),("button",40),("table",41),("caption",11),("thead",42),("tfoot",42),("tbody",42),("colgroup",43),("col",43),("tr",42),("th",44),("td",44),("pcdata",-1),("cdata",-1),("none",-1),("",1)] attList = [["lang","dir","id","xmlns"],["lang","dir","id","profile"],["lang","dir","id"],["href","id"],["href"],["lang","dir","id","http_equiv","name","content","scheme"],["content"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","charset","href","hreflang","type","rel","rev","media"],["lang","dir","id","type","media","title","space"],["type"],["id","charset","type","src","defer","space"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","onload","onunload"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","space"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","cite"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","cite","datetime"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","charset","type","name","href","hreflang","rel","rev","shape","coords"],["id","class","style","title","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","lang","dir"],["dir"],["id","class","style","title"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","declare","classid","codebase","data","type","codetype","archive","standby","height","width","usemap","name","tabindex"],["id","name","value","valuetype","type"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","src","alt","longdesc","height","width","usemap","ismap"],["src"],["alt"],["lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","id","class","style","title","name"],["id"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","shape","coords","href","nohref","alt"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","action","method","enctype","onsubmit","onreset","accept","accept_charset"],["action"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","for","accesskey","onfocus","onblur"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","type","name","value","checked","disabled","readonly","size","maxlength","src","alt","usemap","onselect","onchange","accept"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","name","size","multiple","disabled","tabindex","onfocus","onblur","onchange"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","disabled","label"],["label"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","selected","disabled","label","value"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","name","rows","cols","disabled","readonly","onselect","onchange"],["rows"],["cols"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","name","value","type","disabled"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","summary","width","border","frame","rules","cellspacing","cellpadding"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","align","char","charoff","valign"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","span","width","align","char","charoff","valign"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","abbr","axis","headers","scope","rowspan","colspan","align","char","charoff","valign"]] groups = [[(1,1),(9,27)],[(2,2),(3,99999),(4,99999),(5,99999),(6,2),(7,2),(52,3)],[(77,99999)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(30,4),(31,22),(32,22),(33,99999),(34,22),(35,22),(36,22),(37,22),(38,22),(39,22),(40,22),(41,22),(42,22),(43,22),(44,22),(45,22),(46,22),(47,22),(48,22),(49,22),(50,22),(51,22),(52,3),(53,99999),(54,99999),(55,23),(57,32),(58,22),(59,99999),(60,24),(63,2),(64,33),(66,26),(67,34),(77,99999)],[(7,5),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,17),(54,99999),(55,18),(58,4),(59,99999),(60,19),(63,5),(66,21),(77,99999)],[(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,17),(54,99999),(55,18),(57,11),(58,4),(59,99999),(60,19),(63,5),(64,12),(66,21),(67,13),(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(57,11),(64,12),(67,13)],[(20,6)],[(22,4),(23,6)],[(7,5),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(55,18),(58,4),(59,99999),(60,19),(63,5),(66,21),(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(64,12),(67,13)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,17),(54,99999),(55,18),(57,11),(58,4),(59,99999),(60,19),(63,5),(64,12),(65,4),(66,21),(67,13),(77,99999)],[(68,4),(69,14),(70,14),(71,14),(72,14),(73,99999),(74,16)],[(74,16)],[(73,99999)],[(75,6),(76,6)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,17),(53,99999),(54,99999),(55,18),(57,11),(58,4),(59,99999),(60,19),(63,5),(64,12),(66,21),(67,13),(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(56,99999),(57,11),(64,12),(67,13)],[(61,20),(62,5)],[(62,5)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,17),(54,99999),(55,18),(67,13),(77,99999)],[(7,2),(28,28),(29,28),(30,4),(31,22),(32,22),(33,99999),(34,22),(35,22),(36,22),(37,22),(38,22),(39,22),(40,22),(41,22),(42,22),(43,22),(44,22),(45,22),(46,22),(47,22),(48,22),(49,22),(50,22),(51,22),(52,3),(54,99999),(55,23),(58,22),(59,99999),(60,24),(63,2),(66,26),(77,99999)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(56,99999),(57,32),(64,33),(67,34)],[(61,25),(62,2)],[(62,2)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(31,22),(32,22),(33,99999),(34,22),(35,22),(36,22),(37,22),(38,22),(39,22),(40,22),(41,22),(42,22),(43,22),(44,22),(45,22),(46,22),(47,22),(48,22),(49,22),(50,22),(51,22),(52,3),(54,99999),(55,23),(67,34),(77,99999)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(57,32),(64,33),(67,34)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(30,4),(31,22),(32,22),(33,99999),(34,22),(35,22),(36,22),(37,22),(38,22),(39,22),(40,22),(41,22),(42,22),(43,22),(44,22),(45,22),(46,22),(47,22),(48,22),(49,22),(50,22),(51,22),(52,3),(54,99999),(55,23),(57,32),(58,22),(59,99999),(60,24),(63,2),(64,33),(66,26),(67,34),(77,99999)],[(20,28)],[(22,22),(23,28)],[(7,2),(28,28),(29,28),(30,4),(31,22),(32,22),(33,99999),(34,22),(35,22),(36,22),(37,22),(38,22),(39,22),(40,22),(41,22),(42,22),(43,22),(44,22),(45,22),(46,22),(47,22),(48,22),(49,22),(50,22),(51,22),(55,23),(58,22),(59,99999),(60,24),(63,2),(66,26),(77,99999)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(64,33),(67,34)],[(7,2),(8,27),(10,28),(11,22),(12,22),(13,22),(14,22),(15,22),(16,22),(17,22),(18,29),(19,29),(21,30),(24,22),(25,99999),(26,31),(27,27),(28,28),(29,28),(30,4),(31,22),(32,22),(33,99999),(34,22),(35,22),(36,22),(37,22),(38,22),(39,22),(40,22),(41,22),(42,22),(43,22),(44,22),(45,22),(46,22),(47,22),(48,22),(49,22),(50,22),(51,22),(52,3),(54,99999),(55,23),(57,32),(58,22),(59,99999),(60,24),(63,2),(64,33),(65,22),(66,26),(67,34),(77,99999)],[(68,22),(69,35),(70,35),(71,35),(72,35),(73,99999),(74,37)],[(74,37)],[(73,99999)],[(75,28),(76,28)],[]] -- | 'htmlHelp' provides a way of finding allowed children tags and attributes. For example a @h1@ inside a @body@ tag inside an @html@ tag is queried with -- -- > htmlHelp ["html","body","h1"] -- -- > = [["a","abbr",..,"tt","var"],["alt_att","class_att","dir_att",..,"usemap_att","width_att"]] -- -- which returns a list of 2 elements, each their own list. The first is the allowed children tags, in this case 34. The second is a list of allowed attributes for -- the @h1@ tag. Remember to add a @_@ as a prefix or suffix of all tags, as well as @_bs@ if providing a 'Data.ByteString' to an attribute. -- htmlHelp :: [String] -> [[String]] htmlHelp (x:xs) | (map toLower x) == "html" = htmlHelp2 0 (toNdx "html") xs | otherwise = [["First tag needs to be \"html\"!"]] htmlHelp2 :: Int -> Int -> [String] -> [[String]] htmlHelp2 i lst [] = [ (sort (map (\(t,n)->fst (tagList !! t)) (groups !! i))), sort(map (\a->a++"_att") (attList !! (snd (tagList !! lst))))] htmlHelp2 i lst (x:xs) | n == -1 = [[x ++ " not a child" ++ show (toNdx x)]] | n == 99999 = [[x ++ " can not contain any inner nodes"], sort(map (\a->a++"_att") (attList !! (snd (tagList !! lst))))] | otherwise = htmlHelp2 n (toNdx x) xs where n = getNext (groups !! i) (toNdx x) getNext ((a,b):xs) t | a == t = b | otherwise = getNext xs t getNext [] t = -1 toNdx :: String -> Int toNdx s = toNdx2 s tagList 0 toNdx2 s (x:xs) n | (map toLower s) == (map toLower (fst x)) = n | otherwise = toNdx2 s xs (n+1) toNdx2 s [] _ = (-1)