{-# 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 by building a datastructure based on the DTD. -- Nesting and allowed tags are limited at compile time by recursive types. Required children and child ordering can be enforced at runtime by the -- @chidErrors function. -- -- 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 taking 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 import 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. -- -- module Text.CHXHtml.XHtml1_strict( -- * Validation childErrors, -- * Tag & Attribute Help htmlHelp, -- * Rendering render, render_bs, -- * Tags pcdata, pcdata_bs,s2b, _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, type_att_bs,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,intersperse) import Data.Char import Text.Regex.Posix -- 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 type_att_bs :: B.ByteString -> a instance A_Type Att40 where type_att s = Type_Att_40 (s2b_escape s) type_att_bs = Type_Att_40 instance A_Type Att31 where type_att s = Type_Att_31 (s2b_escape s) type_att_bs = Type_Att_31 instance A_Type Att21 where type_att s = Type_Att_21 (s2b_escape s) type_att_bs = Type_Att_21 instance A_Type Att20 where type_att s = Type_Att_20 (s2b_escape s) type_att_bs = Type_Att_20 instance A_Type Att16 where type_att s = Type_Att_16 (s2b_escape s) type_att_bs = Type_Att_16 instance A_Type Att10 where type_att s = Type_Att_10 (s2b_escape s) type_att_bs = Type_Att_10 instance A_Type Att9 where type_att s = Type_Att_9 (s2b_escape s) type_att_bs = Type_Att_9 instance A_Type Att8 where type_att s = Type_Att_8 (s2b_escape s) type_att_bs = Type_Att_8 instance A_Type Att7 where type_att s = Type_Att_7 (s2b_escape s) type_att_bs = Type_Att_7 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] [Ent6] 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] [Ent6] | Div_3 [Att11] [Ent38] | P_3 [Att11] [Ent30] | H1_3 [Att11] [Ent30] | H2_3 [Att11] [Ent30] | H3_3 [Att11] [Ent30] | H4_3 [Att11] [Ent30] | H5_3 [Att11] [Ent30] | H6_3 [Att11] [Ent30] | Ul_3 [Att11] [Ent7] | Ol_3 [Att11] [Ent7] | Dl_3 [Att11] [Ent8] | Address_3 [Att11] [Ent30] | Hr_3 [Att11] | Pre_3 [Att13] [Ent39] | Blockquote_3 [Att14] [Ent6] | Ins_3 [Att15] [Ent38] | Del_3 [Att15] [Ent38] | A_3 [Att16] [Ent4] | Span_3 [Att11] [Ent30] | Bdo_3 [Att11] [Ent30] | Br_3 [Att19] | Em_3 [Att11] [Ent30] | Strong_3 [Att11] [Ent30] | Dfn_3 [Att11] [Ent30] | Code_3 [Att11] [Ent30] | Samp_3 [Att11] [Ent30] | Kbd_3 [Att11] [Ent30] | Var_3 [Att11] [Ent30] | Cite_3 [Att11] [Ent30] | Abbr_3 [Att11] [Ent30] | Acronym_3 [Att11] [Ent30] | Q_3 [Att14] [Ent30] | Sub_3 [Att11] [Ent30] | Sup_3 [Att11] [Ent30] | Tt_3 [Att11] [Ent30] | I_3 [Att11] [Ent30] | B_3 [Att11] [Ent30] | Big_3 [Att11] [Ent30] | Small_3 [Att11] [Ent30] | Object_3 [Att20] [Ent3] | Param_3 [Att21] | Img_3 [Att22] | Map_3 [Att25] [Ent19] | Form_3 [Att28] [Ent10] | Label_3 [Att30] [Ent31] | Input_3 [Att31] | Select_3 [Att32] [Ent27] | Textarea_3 [Att36] [Ent2] | Fieldset_3 [Att11] [Ent47] | Button_3 [Att40] [Ent29] | Table_3 [Att41] [Ent13] | PCDATA_3 [Att0] B.ByteString deriving (Show) data Ent4 = Script_4 [Att10] [Ent2] | Ins_4 [Att15] [Ent5] | Del_4 [Att15] [Ent5] | 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] [Ent18] | Img_4 [Att22] | Map_4 [Att25] [Ent19] | Label_4 [Att30] [Ent20] | Input_4 [Att31] | Select_4 [Att32] [Ent27] | Textarea_4 [Att36] [Ent2] | Button_4 [Att40] [Ent29] | PCDATA_4 [Att0] B.ByteString deriving (Show) data Ent5 = Script_5 [Att10] [Ent2] | Noscript_5 [Att11] [Ent6] | Div_5 [Att11] [Ent5] | P_5 [Att11] [Ent4] | H1_5 [Att11] [Ent4] | H2_5 [Att11] [Ent4] | H3_5 [Att11] [Ent4] | H4_5 [Att11] [Ent4] | H5_5 [Att11] [Ent4] | H6_5 [Att11] [Ent4] | Ul_5 [Att11] [Ent7] | Ol_5 [Att11] [Ent7] | Dl_5 [Att11] [Ent8] | Address_5 [Att11] [Ent4] | Hr_5 [Att11] | Pre_5 [Att13] [Ent9] | Blockquote_5 [Att14] [Ent6] | Ins_5 [Att15] [Ent5] | Del_5 [Att15] [Ent5] | Span_5 [Att11] [Ent4] | Bdo_5 [Att11] [Ent4] | Br_5 [Att19] | Em_5 [Att11] [Ent4] | Strong_5 [Att11] [Ent4] | Dfn_5 [Att11] [Ent4] | Code_5 [Att11] [Ent4] | Samp_5 [Att11] [Ent4] | Kbd_5 [Att11] [Ent4] | Var_5 [Att11] [Ent4] | Cite_5 [Att11] [Ent4] | Abbr_5 [Att11] [Ent4] | Acronym_5 [Att11] [Ent4] | Q_5 [Att14] [Ent4] | Sub_5 [Att11] [Ent4] | Sup_5 [Att11] [Ent4] | Tt_5 [Att11] [Ent4] | I_5 [Att11] [Ent4] | B_5 [Att11] [Ent4] | Big_5 [Att11] [Ent4] | Small_5 [Att11] [Ent4] | Object_5 [Att20] [Ent18] | Img_5 [Att22] | Map_5 [Att25] [Ent19] | Form_5 [Att28] [Ent10] | Label_5 [Att30] [Ent20] | Input_5 [Att31] | Select_5 [Att32] [Ent27] | Textarea_5 [Att36] [Ent2] | Fieldset_5 [Att11] [Ent17] | Button_5 [Att40] [Ent29] | Table_5 [Att41] [Ent13] | PCDATA_5 [Att0] B.ByteString deriving (Show) data Ent6 = Script_6 [Att10] [Ent2] | Noscript_6 [Att11] [Ent6] | Div_6 [Att11] [Ent5] | 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] [Ent7] | Ol_6 [Att11] [Ent7] | Dl_6 [Att11] [Ent8] | Address_6 [Att11] [Ent4] | Hr_6 [Att11] | Pre_6 [Att13] [Ent9] | Blockquote_6 [Att14] [Ent6] | Ins_6 [Att15] [Ent5] | Del_6 [Att15] [Ent5] | Form_6 [Att28] [Ent10] | Fieldset_6 [Att11] [Ent17] | Table_6 [Att41] [Ent13] deriving (Show) data Ent7 = Li_7 [Att11] [Ent5] deriving (Show) data Ent8 = Dt_8 [Att11] [Ent4] | Dd_8 [Att11] [Ent5] deriving (Show) data Ent9 = Script_9 [Att10] [Ent2] | Ins_9 [Att15] [Ent5] | Del_9 [Att15] [Ent5] | Span_9 [Att11] [Ent4] | Bdo_9 [Att11] [Ent4] | Br_9 [Att19] | Em_9 [Att11] [Ent4] | Strong_9 [Att11] [Ent4] | Dfn_9 [Att11] [Ent4] | Code_9 [Att11] [Ent4] | Samp_9 [Att11] [Ent4] | Kbd_9 [Att11] [Ent4] | Var_9 [Att11] [Ent4] | Cite_9 [Att11] [Ent4] | Abbr_9 [Att11] [Ent4] | Acronym_9 [Att11] [Ent4] | Q_9 [Att14] [Ent4] | Sub_9 [Att11] [Ent4] | Sup_9 [Att11] [Ent4] | Tt_9 [Att11] [Ent4] | I_9 [Att11] [Ent4] | B_9 [Att11] [Ent4] | Big_9 [Att11] [Ent4] | Small_9 [Att11] [Ent4] | Map_9 [Att25] [Ent19] | Label_9 [Att30] [Ent20] | Input_9 [Att31] | Select_9 [Att32] [Ent27] | Textarea_9 [Att36] [Ent2] | Button_9 [Att40] [Ent29] | PCDATA_9 [Att0] B.ByteString deriving (Show) data Ent10 = Script_10 [Att10] [Ent2] | Noscript_10 [Att11] [Ent10] | Div_10 [Att11] [Ent11] | P_10 [Att11] [Ent4] | H1_10 [Att11] [Ent4] | H2_10 [Att11] [Ent4] | H3_10 [Att11] [Ent4] | H4_10 [Att11] [Ent4] | H5_10 [Att11] [Ent4] | H6_10 [Att11] [Ent4] | Ul_10 [Att11] [Ent7] | Ol_10 [Att11] [Ent7] | Dl_10 [Att11] [Ent8] | Address_10 [Att11] [Ent4] | Hr_10 [Att11] | Pre_10 [Att13] [Ent9] | Blockquote_10 [Att14] [Ent10] | Ins_10 [Att15] [Ent11] | Del_10 [Att15] [Ent11] | Fieldset_10 [Att11] [Ent12] | Table_10 [Att41] [Ent13] deriving (Show) data Ent11 = Script_11 [Att10] [Ent2] | Noscript_11 [Att11] [Ent10] | Div_11 [Att11] [Ent11] | 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] [Ent7] | Ol_11 [Att11] [Ent7] | Dl_11 [Att11] [Ent8] | Address_11 [Att11] [Ent4] | Hr_11 [Att11] | Pre_11 [Att13] [Ent9] | Blockquote_11 [Att14] [Ent10] | Ins_11 [Att15] [Ent11] | Del_11 [Att15] [Ent11] | Span_11 [Att11] [Ent4] | Bdo_11 [Att11] [Ent4] | Br_11 [Att19] | Em_11 [Att11] [Ent4] | Strong_11 [Att11] [Ent4] | Dfn_11 [Att11] [Ent4] | Code_11 [Att11] [Ent4] | Samp_11 [Att11] [Ent4] | Kbd_11 [Att11] [Ent4] | Var_11 [Att11] [Ent4] | Cite_11 [Att11] [Ent4] | Abbr_11 [Att11] [Ent4] | Acronym_11 [Att11] [Ent4] | Q_11 [Att14] [Ent4] | Sub_11 [Att11] [Ent4] | Sup_11 [Att11] [Ent4] | Tt_11 [Att11] [Ent4] | I_11 [Att11] [Ent4] | B_11 [Att11] [Ent4] | Big_11 [Att11] [Ent4] | Small_11 [Att11] [Ent4] | Object_11 [Att20] [Ent41] | Img_11 [Att22] | Map_11 [Att25] [Ent42] | Label_11 [Att30] [Ent20] | Input_11 [Att31] | Select_11 [Att32] [Ent27] | Textarea_11 [Att36] [Ent2] | Fieldset_11 [Att11] [Ent12] | Button_11 [Att40] [Ent29] | Table_11 [Att41] [Ent13] | PCDATA_11 [Att0] B.ByteString deriving (Show) data Ent12 = Script_12 [Att10] [Ent2] | Noscript_12 [Att11] [Ent10] | Div_12 [Att11] [Ent11] | 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] [Ent7] | Ol_12 [Att11] [Ent7] | Dl_12 [Att11] [Ent8] | Address_12 [Att11] [Ent4] | Hr_12 [Att11] | Pre_12 [Att13] [Ent9] | Blockquote_12 [Att14] [Ent10] | Ins_12 [Att15] [Ent11] | Del_12 [Att15] [Ent11] | 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] [Ent41] | Img_12 [Att22] | Map_12 [Att25] [Ent42] | Label_12 [Att30] [Ent20] | Input_12 [Att31] | Select_12 [Att32] [Ent27] | Textarea_12 [Att36] [Ent2] | Fieldset_12 [Att11] [Ent12] | Legend_12 [Att39] [Ent4] | Button_12 [Att40] [Ent29] | 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] [Ent15] | 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] [Ent11] | Td_16 [Att44] [Ent11] deriving (Show) data Ent17 = Script_17 [Att10] [Ent2] | Noscript_17 [Att11] [Ent6] | Div_17 [Att11] [Ent5] | 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] [Ent7] | Ol_17 [Att11] [Ent7] | Dl_17 [Att11] [Ent8] | Address_17 [Att11] [Ent4] | Hr_17 [Att11] | Pre_17 [Att13] [Ent9] | Blockquote_17 [Att14] [Ent6] | Ins_17 [Att15] [Ent5] | Del_17 [Att15] [Ent5] | 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] [Ent18] | Img_17 [Att22] | Map_17 [Att25] [Ent19] | Form_17 [Att28] [Ent10] | Label_17 [Att30] [Ent20] | Input_17 [Att31] | Select_17 [Att32] [Ent27] | Textarea_17 [Att36] [Ent2] | Fieldset_17 [Att11] [Ent17] | Legend_17 [Att39] [Ent4] | Button_17 [Att40] [Ent29] | Table_17 [Att41] [Ent13] | PCDATA_17 [Att0] B.ByteString deriving (Show) data Ent18 = Script_18 [Att10] [Ent2] | Noscript_18 [Att11] [Ent6] | Div_18 [Att11] [Ent5] | 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] [Ent7] | Ol_18 [Att11] [Ent7] | Dl_18 [Att11] [Ent8] | Address_18 [Att11] [Ent4] | Hr_18 [Att11] | Pre_18 [Att13] [Ent9] | Blockquote_18 [Att14] [Ent6] | Ins_18 [Att15] [Ent5] | Del_18 [Att15] [Ent5] | Span_18 [Att11] [Ent4] | Bdo_18 [Att11] [Ent4] | Br_18 [Att19] | Em_18 [Att11] [Ent4] | Strong_18 [Att11] [Ent4] | Dfn_18 [Att11] [Ent4] | Code_18 [Att11] [Ent4] | Samp_18 [Att11] [Ent4] | Kbd_18 [Att11] [Ent4] | Var_18 [Att11] [Ent4] | Cite_18 [Att11] [Ent4] | Abbr_18 [Att11] [Ent4] | Acronym_18 [Att11] [Ent4] | Q_18 [Att14] [Ent4] | Sub_18 [Att11] [Ent4] | Sup_18 [Att11] [Ent4] | Tt_18 [Att11] [Ent4] | I_18 [Att11] [Ent4] | B_18 [Att11] [Ent4] | Big_18 [Att11] [Ent4] | Small_18 [Att11] [Ent4] | Object_18 [Att20] [Ent18] | Param_18 [Att21] | Img_18 [Att22] | Map_18 [Att25] [Ent19] | Form_18 [Att28] [Ent10] | Label_18 [Att30] [Ent20] | Input_18 [Att31] | Select_18 [Att32] [Ent27] | Textarea_18 [Att36] [Ent2] | Fieldset_18 [Att11] [Ent17] | Button_18 [Att40] [Ent29] | Table_18 [Att41] [Ent13] | PCDATA_18 [Att0] B.ByteString deriving (Show) data Ent19 = Script_19 [Att10] [Ent2] | Noscript_19 [Att11] [Ent6] | Div_19 [Att11] [Ent5] | P_19 [Att11] [Ent4] | H1_19 [Att11] [Ent4] | H2_19 [Att11] [Ent4] | H3_19 [Att11] [Ent4] | H4_19 [Att11] [Ent4] | H5_19 [Att11] [Ent4] | H6_19 [Att11] [Ent4] | Ul_19 [Att11] [Ent7] | Ol_19 [Att11] [Ent7] | Dl_19 [Att11] [Ent8] | Address_19 [Att11] [Ent4] | Hr_19 [Att11] | Pre_19 [Att13] [Ent9] | Blockquote_19 [Att14] [Ent6] | Ins_19 [Att15] [Ent5] | Del_19 [Att15] [Ent5] | Area_19 [Att27] | Form_19 [Att28] [Ent10] | Fieldset_19 [Att11] [Ent17] | Table_19 [Att41] [Ent13] deriving (Show) data Ent20 = Script_20 [Att10] [Ent2] | Ins_20 [Att15] [Ent21] | Del_20 [Att15] [Ent21] | Span_20 [Att11] [Ent20] | Bdo_20 [Att11] [Ent20] | Br_20 [Att19] | Em_20 [Att11] [Ent20] | Strong_20 [Att11] [Ent20] | Dfn_20 [Att11] [Ent20] | Code_20 [Att11] [Ent20] | Samp_20 [Att11] [Ent20] | Kbd_20 [Att11] [Ent20] | Var_20 [Att11] [Ent20] | Cite_20 [Att11] [Ent20] | Abbr_20 [Att11] [Ent20] | Acronym_20 [Att11] [Ent20] | Q_20 [Att14] [Ent20] | Sub_20 [Att11] [Ent20] | Sup_20 [Att11] [Ent20] | Tt_20 [Att11] [Ent20] | I_20 [Att11] [Ent20] | B_20 [Att11] [Ent20] | Big_20 [Att11] [Ent20] | Small_20 [Att11] [Ent20] | Object_20 [Att20] [Ent26] | Img_20 [Att22] | Map_20 [Att25] [Ent19] | Input_20 [Att31] | Select_20 [Att32] [Ent27] | Textarea_20 [Att36] [Ent2] | Button_20 [Att40] [Ent29] | PCDATA_20 [Att0] B.ByteString deriving (Show) data Ent21 = Script_21 [Att10] [Ent2] | Noscript_21 [Att11] [Ent6] | Div_21 [Att11] [Ent21] | P_21 [Att11] [Ent20] | H1_21 [Att11] [Ent20] | H2_21 [Att11] [Ent20] | H3_21 [Att11] [Ent20] | H4_21 [Att11] [Ent20] | H5_21 [Att11] [Ent20] | H6_21 [Att11] [Ent20] | Ul_21 [Att11] [Ent7] | Ol_21 [Att11] [Ent7] | Dl_21 [Att11] [Ent8] | Address_21 [Att11] [Ent20] | Hr_21 [Att11] | Pre_21 [Att13] [Ent22] | Blockquote_21 [Att14] [Ent6] | Ins_21 [Att15] [Ent21] | Del_21 [Att15] [Ent21] | Span_21 [Att11] [Ent20] | Bdo_21 [Att11] [Ent20] | Br_21 [Att19] | Em_21 [Att11] [Ent20] | Strong_21 [Att11] [Ent20] | Dfn_21 [Att11] [Ent20] | Code_21 [Att11] [Ent20] | Samp_21 [Att11] [Ent20] | Kbd_21 [Att11] [Ent20] | Var_21 [Att11] [Ent20] | Cite_21 [Att11] [Ent20] | Abbr_21 [Att11] [Ent20] | Acronym_21 [Att11] [Ent20] | Q_21 [Att14] [Ent20] | Sub_21 [Att11] [Ent20] | Sup_21 [Att11] [Ent20] | Tt_21 [Att11] [Ent20] | I_21 [Att11] [Ent20] | B_21 [Att11] [Ent20] | Big_21 [Att11] [Ent20] | Small_21 [Att11] [Ent20] | Object_21 [Att20] [Ent26] | Img_21 [Att22] | Map_21 [Att25] [Ent19] | Form_21 [Att28] [Ent10] | Input_21 [Att31] | Select_21 [Att32] [Ent27] | Textarea_21 [Att36] [Ent2] | Fieldset_21 [Att11] [Ent25] | Button_21 [Att40] [Ent29] | Table_21 [Att41] [Ent13] | PCDATA_21 [Att0] B.ByteString deriving (Show) data Ent22 = Script_22 [Att10] [Ent2] | Ins_22 [Att15] [Ent21] | Del_22 [Att15] [Ent21] | Span_22 [Att11] [Ent20] | Bdo_22 [Att11] [Ent20] | Br_22 [Att19] | Em_22 [Att11] [Ent20] | Strong_22 [Att11] [Ent20] | Dfn_22 [Att11] [Ent20] | Code_22 [Att11] [Ent20] | Samp_22 [Att11] [Ent20] | Kbd_22 [Att11] [Ent20] | Var_22 [Att11] [Ent20] | Cite_22 [Att11] [Ent20] | Abbr_22 [Att11] [Ent20] | Acronym_22 [Att11] [Ent20] | Q_22 [Att14] [Ent20] | Sub_22 [Att11] [Ent20] | Sup_22 [Att11] [Ent20] | Tt_22 [Att11] [Ent20] | I_22 [Att11] [Ent20] | B_22 [Att11] [Ent20] | Big_22 [Att11] [Ent20] | Small_22 [Att11] [Ent20] | Map_22 [Att25] [Ent19] | Input_22 [Att31] | Select_22 [Att32] [Ent27] | Textarea_22 [Att36] [Ent2] | Button_22 [Att40] [Ent29] | PCDATA_22 [Att0] B.ByteString deriving (Show) data Ent23 = Script_23 [Att10] [Ent2] | Noscript_23 [Att11] [Ent10] | Div_23 [Att11] [Ent23] | P_23 [Att11] [Ent20] | H1_23 [Att11] [Ent20] | H2_23 [Att11] [Ent20] | H3_23 [Att11] [Ent20] | H4_23 [Att11] [Ent20] | H5_23 [Att11] [Ent20] | H6_23 [Att11] [Ent20] | Ul_23 [Att11] [Ent7] | Ol_23 [Att11] [Ent7] | Dl_23 [Att11] [Ent8] | Address_23 [Att11] [Ent20] | Hr_23 [Att11] | Pre_23 [Att13] [Ent22] | Blockquote_23 [Att14] [Ent10] | Ins_23 [Att15] [Ent23] | Del_23 [Att15] [Ent23] | Span_23 [Att11] [Ent20] | Bdo_23 [Att11] [Ent20] | Br_23 [Att19] | Em_23 [Att11] [Ent20] | Strong_23 [Att11] [Ent20] | Dfn_23 [Att11] [Ent20] | Code_23 [Att11] [Ent20] | Samp_23 [Att11] [Ent20] | Kbd_23 [Att11] [Ent20] | Var_23 [Att11] [Ent20] | Cite_23 [Att11] [Ent20] | Abbr_23 [Att11] [Ent20] | Acronym_23 [Att11] [Ent20] | Q_23 [Att14] [Ent20] | Sub_23 [Att11] [Ent20] | Sup_23 [Att11] [Ent20] | Tt_23 [Att11] [Ent20] | I_23 [Att11] [Ent20] | B_23 [Att11] [Ent20] | Big_23 [Att11] [Ent20] | Small_23 [Att11] [Ent20] | Object_23 [Att20] [Ent43] | Img_23 [Att22] | Map_23 [Att25] [Ent42] | Input_23 [Att31] | Select_23 [Att32] [Ent27] | Textarea_23 [Att36] [Ent2] | Fieldset_23 [Att11] [Ent24] | Button_23 [Att40] [Ent29] | Table_23 [Att41] [Ent13] | PCDATA_23 [Att0] B.ByteString deriving (Show) data Ent24 = Script_24 [Att10] [Ent2] | Noscript_24 [Att11] [Ent10] | Div_24 [Att11] [Ent23] | P_24 [Att11] [Ent20] | H1_24 [Att11] [Ent20] | H2_24 [Att11] [Ent20] | H3_24 [Att11] [Ent20] | H4_24 [Att11] [Ent20] | H5_24 [Att11] [Ent20] | H6_24 [Att11] [Ent20] | Ul_24 [Att11] [Ent7] | Ol_24 [Att11] [Ent7] | Dl_24 [Att11] [Ent8] | Address_24 [Att11] [Ent20] | Hr_24 [Att11] | Pre_24 [Att13] [Ent22] | Blockquote_24 [Att14] [Ent10] | Ins_24 [Att15] [Ent23] | Del_24 [Att15] [Ent23] | Span_24 [Att11] [Ent20] | Bdo_24 [Att11] [Ent20] | Br_24 [Att19] | Em_24 [Att11] [Ent20] | Strong_24 [Att11] [Ent20] | Dfn_24 [Att11] [Ent20] | Code_24 [Att11] [Ent20] | Samp_24 [Att11] [Ent20] | Kbd_24 [Att11] [Ent20] | Var_24 [Att11] [Ent20] | Cite_24 [Att11] [Ent20] | Abbr_24 [Att11] [Ent20] | Acronym_24 [Att11] [Ent20] | Q_24 [Att14] [Ent20] | Sub_24 [Att11] [Ent20] | Sup_24 [Att11] [Ent20] | Tt_24 [Att11] [Ent20] | I_24 [Att11] [Ent20] | B_24 [Att11] [Ent20] | Big_24 [Att11] [Ent20] | Small_24 [Att11] [Ent20] | Object_24 [Att20] [Ent43] | Img_24 [Att22] | Map_24 [Att25] [Ent42] | Input_24 [Att31] | Select_24 [Att32] [Ent27] | Textarea_24 [Att36] [Ent2] | Fieldset_24 [Att11] [Ent24] | Legend_24 [Att39] [Ent20] | Button_24 [Att40] [Ent29] | Table_24 [Att41] [Ent13] | PCDATA_24 [Att0] B.ByteString deriving (Show) data Ent25 = Script_25 [Att10] [Ent2] | Noscript_25 [Att11] [Ent6] | Div_25 [Att11] [Ent21] | P_25 [Att11] [Ent20] | H1_25 [Att11] [Ent20] | H2_25 [Att11] [Ent20] | H3_25 [Att11] [Ent20] | H4_25 [Att11] [Ent20] | H5_25 [Att11] [Ent20] | H6_25 [Att11] [Ent20] | Ul_25 [Att11] [Ent7] | Ol_25 [Att11] [Ent7] | Dl_25 [Att11] [Ent8] | Address_25 [Att11] [Ent20] | Hr_25 [Att11] | Pre_25 [Att13] [Ent22] | Blockquote_25 [Att14] [Ent6] | Ins_25 [Att15] [Ent21] | Del_25 [Att15] [Ent21] | Span_25 [Att11] [Ent20] | Bdo_25 [Att11] [Ent20] | Br_25 [Att19] | Em_25 [Att11] [Ent20] | Strong_25 [Att11] [Ent20] | Dfn_25 [Att11] [Ent20] | Code_25 [Att11] [Ent20] | Samp_25 [Att11] [Ent20] | Kbd_25 [Att11] [Ent20] | Var_25 [Att11] [Ent20] | Cite_25 [Att11] [Ent20] | Abbr_25 [Att11] [Ent20] | Acronym_25 [Att11] [Ent20] | Q_25 [Att14] [Ent20] | Sub_25 [Att11] [Ent20] | Sup_25 [Att11] [Ent20] | Tt_25 [Att11] [Ent20] | I_25 [Att11] [Ent20] | B_25 [Att11] [Ent20] | Big_25 [Att11] [Ent20] | Small_25 [Att11] [Ent20] | Object_25 [Att20] [Ent26] | Img_25 [Att22] | Map_25 [Att25] [Ent19] | Form_25 [Att28] [Ent10] | Input_25 [Att31] | Select_25 [Att32] [Ent27] | Textarea_25 [Att36] [Ent2] | Fieldset_25 [Att11] [Ent25] | Legend_25 [Att39] [Ent20] | Button_25 [Att40] [Ent29] | Table_25 [Att41] [Ent13] | PCDATA_25 [Att0] B.ByteString deriving (Show) data Ent26 = Script_26 [Att10] [Ent2] | Noscript_26 [Att11] [Ent6] | Div_26 [Att11] [Ent21] | P_26 [Att11] [Ent20] | H1_26 [Att11] [Ent20] | H2_26 [Att11] [Ent20] | H3_26 [Att11] [Ent20] | H4_26 [Att11] [Ent20] | H5_26 [Att11] [Ent20] | H6_26 [Att11] [Ent20] | Ul_26 [Att11] [Ent7] | Ol_26 [Att11] [Ent7] | Dl_26 [Att11] [Ent8] | Address_26 [Att11] [Ent20] | Hr_26 [Att11] | Pre_26 [Att13] [Ent22] | Blockquote_26 [Att14] [Ent6] | Ins_26 [Att15] [Ent21] | Del_26 [Att15] [Ent21] | Span_26 [Att11] [Ent20] | Bdo_26 [Att11] [Ent20] | Br_26 [Att19] | Em_26 [Att11] [Ent20] | Strong_26 [Att11] [Ent20] | Dfn_26 [Att11] [Ent20] | Code_26 [Att11] [Ent20] | Samp_26 [Att11] [Ent20] | Kbd_26 [Att11] [Ent20] | Var_26 [Att11] [Ent20] | Cite_26 [Att11] [Ent20] | Abbr_26 [Att11] [Ent20] | Acronym_26 [Att11] [Ent20] | Q_26 [Att14] [Ent20] | Sub_26 [Att11] [Ent20] | Sup_26 [Att11] [Ent20] | Tt_26 [Att11] [Ent20] | I_26 [Att11] [Ent20] | B_26 [Att11] [Ent20] | Big_26 [Att11] [Ent20] | Small_26 [Att11] [Ent20] | Object_26 [Att20] [Ent26] | Param_26 [Att21] | Img_26 [Att22] | Map_26 [Att25] [Ent19] | Form_26 [Att28] [Ent10] | Input_26 [Att31] | Select_26 [Att32] [Ent27] | Textarea_26 [Att36] [Ent2] | Fieldset_26 [Att11] [Ent25] | Button_26 [Att40] [Ent29] | Table_26 [Att41] [Ent13] | PCDATA_26 [Att0] B.ByteString deriving (Show) data Ent27 = Optgroup_27 [Att33] [Ent28] | Option_27 [Att35] [Ent2] deriving (Show) data Ent28 = Option_28 [Att35] [Ent2] deriving (Show) data Ent29 = Script_29 [Att10] [Ent2] | Noscript_29 [Att11] [Ent6] | Div_29 [Att11] [Ent21] | P_29 [Att11] [Ent20] | H1_29 [Att11] [Ent20] | H2_29 [Att11] [Ent20] | H3_29 [Att11] [Ent20] | H4_29 [Att11] [Ent20] | H5_29 [Att11] [Ent20] | H6_29 [Att11] [Ent20] | Ul_29 [Att11] [Ent7] | Ol_29 [Att11] [Ent7] | Dl_29 [Att11] [Ent8] | Address_29 [Att11] [Ent20] | Hr_29 [Att11] | Pre_29 [Att13] [Ent22] | Blockquote_29 [Att14] [Ent6] | Ins_29 [Att15] [Ent21] | Del_29 [Att15] [Ent21] | Span_29 [Att11] [Ent20] | Bdo_29 [Att11] [Ent20] | Br_29 [Att19] | Em_29 [Att11] [Ent20] | Strong_29 [Att11] [Ent20] | Dfn_29 [Att11] [Ent20] | Code_29 [Att11] [Ent20] | Samp_29 [Att11] [Ent20] | Kbd_29 [Att11] [Ent20] | Var_29 [Att11] [Ent20] | Cite_29 [Att11] [Ent20] | Abbr_29 [Att11] [Ent20] | Acronym_29 [Att11] [Ent20] | Q_29 [Att14] [Ent20] | Sub_29 [Att11] [Ent20] | Sup_29 [Att11] [Ent20] | Tt_29 [Att11] [Ent20] | I_29 [Att11] [Ent20] | B_29 [Att11] [Ent20] | Big_29 [Att11] [Ent20] | Small_29 [Att11] [Ent20] | Object_29 [Att20] [Ent26] | Img_29 [Att22] | Map_29 [Att25] [Ent19] | Table_29 [Att41] [Ent13] | PCDATA_29 [Att0] B.ByteString deriving (Show) data Ent30 = Script_30 [Att10] [Ent2] | Ins_30 [Att15] [Ent38] | Del_30 [Att15] [Ent38] | A_30 [Att16] [Ent4] | Span_30 [Att11] [Ent30] | Bdo_30 [Att11] [Ent30] | Br_30 [Att19] | Em_30 [Att11] [Ent30] | Strong_30 [Att11] [Ent30] | Dfn_30 [Att11] [Ent30] | Code_30 [Att11] [Ent30] | Samp_30 [Att11] [Ent30] | Kbd_30 [Att11] [Ent30] | Var_30 [Att11] [Ent30] | Cite_30 [Att11] [Ent30] | Abbr_30 [Att11] [Ent30] | Acronym_30 [Att11] [Ent30] | Q_30 [Att14] [Ent30] | Sub_30 [Att11] [Ent30] | Sup_30 [Att11] [Ent30] | Tt_30 [Att11] [Ent30] | I_30 [Att11] [Ent30] | B_30 [Att11] [Ent30] | Big_30 [Att11] [Ent30] | Small_30 [Att11] [Ent30] | Object_30 [Att20] [Ent3] | Img_30 [Att22] | Map_30 [Att25] [Ent19] | Label_30 [Att30] [Ent31] | Input_30 [Att31] | Select_30 [Att32] [Ent27] | Textarea_30 [Att36] [Ent2] | Button_30 [Att40] [Ent29] | PCDATA_30 [Att0] B.ByteString deriving (Show) data Ent31 = Script_31 [Att10] [Ent2] | Ins_31 [Att15] [Ent32] | Del_31 [Att15] [Ent32] | A_31 [Att16] [Ent20] | Span_31 [Att11] [Ent31] | Bdo_31 [Att11] [Ent31] | Br_31 [Att19] | Em_31 [Att11] [Ent31] | Strong_31 [Att11] [Ent31] | Dfn_31 [Att11] [Ent31] | Code_31 [Att11] [Ent31] | Samp_31 [Att11] [Ent31] | Kbd_31 [Att11] [Ent31] | Var_31 [Att11] [Ent31] | Cite_31 [Att11] [Ent31] | Abbr_31 [Att11] [Ent31] | Acronym_31 [Att11] [Ent31] | Q_31 [Att14] [Ent31] | Sub_31 [Att11] [Ent31] | Sup_31 [Att11] [Ent31] | Tt_31 [Att11] [Ent31] | I_31 [Att11] [Ent31] | B_31 [Att11] [Ent31] | Big_31 [Att11] [Ent31] | Small_31 [Att11] [Ent31] | Object_31 [Att20] [Ent37] | Img_31 [Att22] | Map_31 [Att25] [Ent19] | Input_31 [Att31] | Select_31 [Att32] [Ent27] | Textarea_31 [Att36] [Ent2] | Button_31 [Att40] [Ent29] | PCDATA_31 [Att0] B.ByteString deriving (Show) data Ent32 = Script_32 [Att10] [Ent2] | Noscript_32 [Att11] [Ent6] | Div_32 [Att11] [Ent32] | P_32 [Att11] [Ent31] | H1_32 [Att11] [Ent31] | H2_32 [Att11] [Ent31] | H3_32 [Att11] [Ent31] | H4_32 [Att11] [Ent31] | H5_32 [Att11] [Ent31] | H6_32 [Att11] [Ent31] | Ul_32 [Att11] [Ent7] | Ol_32 [Att11] [Ent7] | Dl_32 [Att11] [Ent8] | Address_32 [Att11] [Ent31] | Hr_32 [Att11] | Pre_32 [Att13] [Ent33] | Blockquote_32 [Att14] [Ent6] | Ins_32 [Att15] [Ent32] | Del_32 [Att15] [Ent32] | A_32 [Att16] [Ent20] | Span_32 [Att11] [Ent31] | Bdo_32 [Att11] [Ent31] | Br_32 [Att19] | Em_32 [Att11] [Ent31] | Strong_32 [Att11] [Ent31] | Dfn_32 [Att11] [Ent31] | Code_32 [Att11] [Ent31] | Samp_32 [Att11] [Ent31] | Kbd_32 [Att11] [Ent31] | Var_32 [Att11] [Ent31] | Cite_32 [Att11] [Ent31] | Abbr_32 [Att11] [Ent31] | Acronym_32 [Att11] [Ent31] | Q_32 [Att14] [Ent31] | Sub_32 [Att11] [Ent31] | Sup_32 [Att11] [Ent31] | Tt_32 [Att11] [Ent31] | I_32 [Att11] [Ent31] | B_32 [Att11] [Ent31] | Big_32 [Att11] [Ent31] | Small_32 [Att11] [Ent31] | Object_32 [Att20] [Ent37] | Img_32 [Att22] | Map_32 [Att25] [Ent19] | Form_32 [Att28] [Ent10] | Input_32 [Att31] | Select_32 [Att32] [Ent27] | Textarea_32 [Att36] [Ent2] | Fieldset_32 [Att11] [Ent36] | Button_32 [Att40] [Ent29] | Table_32 [Att41] [Ent13] | PCDATA_32 [Att0] B.ByteString deriving (Show) data Ent33 = Script_33 [Att10] [Ent2] | Ins_33 [Att15] [Ent32] | Del_33 [Att15] [Ent32] | A_33 [Att16] [Ent20] | Span_33 [Att11] [Ent31] | Bdo_33 [Att11] [Ent31] | Br_33 [Att19] | Em_33 [Att11] [Ent31] | Strong_33 [Att11] [Ent31] | Dfn_33 [Att11] [Ent31] | Code_33 [Att11] [Ent31] | Samp_33 [Att11] [Ent31] | Kbd_33 [Att11] [Ent31] | Var_33 [Att11] [Ent31] | Cite_33 [Att11] [Ent31] | Abbr_33 [Att11] [Ent31] | Acronym_33 [Att11] [Ent31] | Q_33 [Att14] [Ent31] | Sub_33 [Att11] [Ent31] | Sup_33 [Att11] [Ent31] | Tt_33 [Att11] [Ent31] | I_33 [Att11] [Ent31] | B_33 [Att11] [Ent31] | Big_33 [Att11] [Ent31] | Small_33 [Att11] [Ent31] | Map_33 [Att25] [Ent19] | Input_33 [Att31] | Select_33 [Att32] [Ent27] | Textarea_33 [Att36] [Ent2] | Button_33 [Att40] [Ent29] | PCDATA_33 [Att0] B.ByteString deriving (Show) data Ent34 = Script_34 [Att10] [Ent2] | Noscript_34 [Att11] [Ent10] | Div_34 [Att11] [Ent34] | P_34 [Att11] [Ent31] | H1_34 [Att11] [Ent31] | H2_34 [Att11] [Ent31] | H3_34 [Att11] [Ent31] | H4_34 [Att11] [Ent31] | H5_34 [Att11] [Ent31] | H6_34 [Att11] [Ent31] | Ul_34 [Att11] [Ent7] | Ol_34 [Att11] [Ent7] | Dl_34 [Att11] [Ent8] | Address_34 [Att11] [Ent31] | Hr_34 [Att11] | Pre_34 [Att13] [Ent33] | Blockquote_34 [Att14] [Ent10] | Ins_34 [Att15] [Ent34] | Del_34 [Att15] [Ent34] | A_34 [Att16] [Ent20] | Span_34 [Att11] [Ent31] | Bdo_34 [Att11] [Ent31] | Br_34 [Att19] | Em_34 [Att11] [Ent31] | Strong_34 [Att11] [Ent31] | Dfn_34 [Att11] [Ent31] | Code_34 [Att11] [Ent31] | Samp_34 [Att11] [Ent31] | Kbd_34 [Att11] [Ent31] | Var_34 [Att11] [Ent31] | Cite_34 [Att11] [Ent31] | Abbr_34 [Att11] [Ent31] | Acronym_34 [Att11] [Ent31] | Q_34 [Att14] [Ent31] | Sub_34 [Att11] [Ent31] | Sup_34 [Att11] [Ent31] | Tt_34 [Att11] [Ent31] | I_34 [Att11] [Ent31] | B_34 [Att11] [Ent31] | Big_34 [Att11] [Ent31] | Small_34 [Att11] [Ent31] | Object_34 [Att20] [Ent45] | Img_34 [Att22] | Map_34 [Att25] [Ent42] | Input_34 [Att31] | Select_34 [Att32] [Ent27] | Textarea_34 [Att36] [Ent2] | Fieldset_34 [Att11] [Ent35] | Button_34 [Att40] [Ent29] | Table_34 [Att41] [Ent13] | PCDATA_34 [Att0] B.ByteString deriving (Show) data Ent35 = Script_35 [Att10] [Ent2] | Noscript_35 [Att11] [Ent10] | Div_35 [Att11] [Ent34] | P_35 [Att11] [Ent31] | H1_35 [Att11] [Ent31] | H2_35 [Att11] [Ent31] | H3_35 [Att11] [Ent31] | H4_35 [Att11] [Ent31] | H5_35 [Att11] [Ent31] | H6_35 [Att11] [Ent31] | Ul_35 [Att11] [Ent7] | Ol_35 [Att11] [Ent7] | Dl_35 [Att11] [Ent8] | Address_35 [Att11] [Ent31] | Hr_35 [Att11] | Pre_35 [Att13] [Ent33] | Blockquote_35 [Att14] [Ent10] | Ins_35 [Att15] [Ent34] | Del_35 [Att15] [Ent34] | A_35 [Att16] [Ent20] | Span_35 [Att11] [Ent31] | Bdo_35 [Att11] [Ent31] | Br_35 [Att19] | Em_35 [Att11] [Ent31] | Strong_35 [Att11] [Ent31] | Dfn_35 [Att11] [Ent31] | Code_35 [Att11] [Ent31] | Samp_35 [Att11] [Ent31] | Kbd_35 [Att11] [Ent31] | Var_35 [Att11] [Ent31] | Cite_35 [Att11] [Ent31] | Abbr_35 [Att11] [Ent31] | Acronym_35 [Att11] [Ent31] | Q_35 [Att14] [Ent31] | Sub_35 [Att11] [Ent31] | Sup_35 [Att11] [Ent31] | Tt_35 [Att11] [Ent31] | I_35 [Att11] [Ent31] | B_35 [Att11] [Ent31] | Big_35 [Att11] [Ent31] | Small_35 [Att11] [Ent31] | Object_35 [Att20] [Ent45] | Img_35 [Att22] | Map_35 [Att25] [Ent42] | Input_35 [Att31] | Select_35 [Att32] [Ent27] | Textarea_35 [Att36] [Ent2] | Fieldset_35 [Att11] [Ent35] | Legend_35 [Att39] [Ent31] | Button_35 [Att40] [Ent29] | Table_35 [Att41] [Ent13] | PCDATA_35 [Att0] B.ByteString deriving (Show) data Ent36 = Script_36 [Att10] [Ent2] | Noscript_36 [Att11] [Ent6] | Div_36 [Att11] [Ent32] | P_36 [Att11] [Ent31] | H1_36 [Att11] [Ent31] | H2_36 [Att11] [Ent31] | H3_36 [Att11] [Ent31] | H4_36 [Att11] [Ent31] | H5_36 [Att11] [Ent31] | H6_36 [Att11] [Ent31] | Ul_36 [Att11] [Ent7] | Ol_36 [Att11] [Ent7] | Dl_36 [Att11] [Ent8] | Address_36 [Att11] [Ent31] | Hr_36 [Att11] | Pre_36 [Att13] [Ent33] | Blockquote_36 [Att14] [Ent6] | Ins_36 [Att15] [Ent32] | Del_36 [Att15] [Ent32] | A_36 [Att16] [Ent20] | Span_36 [Att11] [Ent31] | Bdo_36 [Att11] [Ent31] | Br_36 [Att19] | Em_36 [Att11] [Ent31] | Strong_36 [Att11] [Ent31] | Dfn_36 [Att11] [Ent31] | Code_36 [Att11] [Ent31] | Samp_36 [Att11] [Ent31] | Kbd_36 [Att11] [Ent31] | Var_36 [Att11] [Ent31] | Cite_36 [Att11] [Ent31] | Abbr_36 [Att11] [Ent31] | Acronym_36 [Att11] [Ent31] | Q_36 [Att14] [Ent31] | Sub_36 [Att11] [Ent31] | Sup_36 [Att11] [Ent31] | Tt_36 [Att11] [Ent31] | I_36 [Att11] [Ent31] | B_36 [Att11] [Ent31] | Big_36 [Att11] [Ent31] | Small_36 [Att11] [Ent31] | Object_36 [Att20] [Ent37] | Img_36 [Att22] | Map_36 [Att25] [Ent19] | Form_36 [Att28] [Ent10] | Input_36 [Att31] | Select_36 [Att32] [Ent27] | Textarea_36 [Att36] [Ent2] | Fieldset_36 [Att11] [Ent36] | Legend_36 [Att39] [Ent31] | Button_36 [Att40] [Ent29] | Table_36 [Att41] [Ent13] | PCDATA_36 [Att0] B.ByteString deriving (Show) data Ent37 = Script_37 [Att10] [Ent2] | Noscript_37 [Att11] [Ent6] | Div_37 [Att11] [Ent32] | P_37 [Att11] [Ent31] | H1_37 [Att11] [Ent31] | H2_37 [Att11] [Ent31] | H3_37 [Att11] [Ent31] | H4_37 [Att11] [Ent31] | H5_37 [Att11] [Ent31] | H6_37 [Att11] [Ent31] | Ul_37 [Att11] [Ent7] | Ol_37 [Att11] [Ent7] | Dl_37 [Att11] [Ent8] | Address_37 [Att11] [Ent31] | Hr_37 [Att11] | Pre_37 [Att13] [Ent33] | Blockquote_37 [Att14] [Ent6] | Ins_37 [Att15] [Ent32] | Del_37 [Att15] [Ent32] | A_37 [Att16] [Ent20] | Span_37 [Att11] [Ent31] | Bdo_37 [Att11] [Ent31] | Br_37 [Att19] | Em_37 [Att11] [Ent31] | Strong_37 [Att11] [Ent31] | Dfn_37 [Att11] [Ent31] | Code_37 [Att11] [Ent31] | Samp_37 [Att11] [Ent31] | Kbd_37 [Att11] [Ent31] | Var_37 [Att11] [Ent31] | Cite_37 [Att11] [Ent31] | Abbr_37 [Att11] [Ent31] | Acronym_37 [Att11] [Ent31] | Q_37 [Att14] [Ent31] | Sub_37 [Att11] [Ent31] | Sup_37 [Att11] [Ent31] | Tt_37 [Att11] [Ent31] | I_37 [Att11] [Ent31] | B_37 [Att11] [Ent31] | Big_37 [Att11] [Ent31] | Small_37 [Att11] [Ent31] | Object_37 [Att20] [Ent37] | Param_37 [Att21] | Img_37 [Att22] | Map_37 [Att25] [Ent19] | Form_37 [Att28] [Ent10] | Input_37 [Att31] | Select_37 [Att32] [Ent27] | Textarea_37 [Att36] [Ent2] | Fieldset_37 [Att11] [Ent36] | Button_37 [Att40] [Ent29] | Table_37 [Att41] [Ent13] | PCDATA_37 [Att0] B.ByteString deriving (Show) data Ent38 = Script_38 [Att10] [Ent2] | Noscript_38 [Att11] [Ent6] | Div_38 [Att11] [Ent38] | P_38 [Att11] [Ent30] | H1_38 [Att11] [Ent30] | H2_38 [Att11] [Ent30] | H3_38 [Att11] [Ent30] | H4_38 [Att11] [Ent30] | H5_38 [Att11] [Ent30] | H6_38 [Att11] [Ent30] | Ul_38 [Att11] [Ent7] | Ol_38 [Att11] [Ent7] | Dl_38 [Att11] [Ent8] | Address_38 [Att11] [Ent30] | Hr_38 [Att11] | Pre_38 [Att13] [Ent39] | Blockquote_38 [Att14] [Ent6] | Ins_38 [Att15] [Ent38] | Del_38 [Att15] [Ent38] | A_38 [Att16] [Ent4] | Span_38 [Att11] [Ent30] | Bdo_38 [Att11] [Ent30] | Br_38 [Att19] | Em_38 [Att11] [Ent30] | Strong_38 [Att11] [Ent30] | Dfn_38 [Att11] [Ent30] | Code_38 [Att11] [Ent30] | Samp_38 [Att11] [Ent30] | Kbd_38 [Att11] [Ent30] | Var_38 [Att11] [Ent30] | Cite_38 [Att11] [Ent30] | Abbr_38 [Att11] [Ent30] | Acronym_38 [Att11] [Ent30] | Q_38 [Att14] [Ent30] | Sub_38 [Att11] [Ent30] | Sup_38 [Att11] [Ent30] | Tt_38 [Att11] [Ent30] | I_38 [Att11] [Ent30] | B_38 [Att11] [Ent30] | Big_38 [Att11] [Ent30] | Small_38 [Att11] [Ent30] | Object_38 [Att20] [Ent3] | Img_38 [Att22] | Map_38 [Att25] [Ent19] | Form_38 [Att28] [Ent10] | Label_38 [Att30] [Ent31] | Input_38 [Att31] | Select_38 [Att32] [Ent27] | Textarea_38 [Att36] [Ent2] | Fieldset_38 [Att11] [Ent47] | Button_38 [Att40] [Ent29] | Table_38 [Att41] [Ent13] | PCDATA_38 [Att0] B.ByteString deriving (Show) data Ent39 = Script_39 [Att10] [Ent2] | Ins_39 [Att15] [Ent38] | Del_39 [Att15] [Ent38] | A_39 [Att16] [Ent4] | Span_39 [Att11] [Ent30] | Bdo_39 [Att11] [Ent30] | Br_39 [Att19] | Em_39 [Att11] [Ent30] | Strong_39 [Att11] [Ent30] | Dfn_39 [Att11] [Ent30] | Code_39 [Att11] [Ent30] | Samp_39 [Att11] [Ent30] | Kbd_39 [Att11] [Ent30] | Var_39 [Att11] [Ent30] | Cite_39 [Att11] [Ent30] | Abbr_39 [Att11] [Ent30] | Acronym_39 [Att11] [Ent30] | Q_39 [Att14] [Ent30] | Sub_39 [Att11] [Ent30] | Sup_39 [Att11] [Ent30] | Tt_39 [Att11] [Ent30] | I_39 [Att11] [Ent30] | B_39 [Att11] [Ent30] | Big_39 [Att11] [Ent30] | Small_39 [Att11] [Ent30] | Map_39 [Att25] [Ent19] | Label_39 [Att30] [Ent31] | Input_39 [Att31] | Select_39 [Att32] [Ent27] | Textarea_39 [Att36] [Ent2] | Button_39 [Att40] [Ent29] | PCDATA_39 [Att0] B.ByteString deriving (Show) data Ent40 = Script_40 [Att10] [Ent2] | Noscript_40 [Att11] [Ent10] | Div_40 [Att11] [Ent40] | P_40 [Att11] [Ent30] | H1_40 [Att11] [Ent30] | H2_40 [Att11] [Ent30] | H3_40 [Att11] [Ent30] | H4_40 [Att11] [Ent30] | H5_40 [Att11] [Ent30] | H6_40 [Att11] [Ent30] | Ul_40 [Att11] [Ent7] | Ol_40 [Att11] [Ent7] | Dl_40 [Att11] [Ent8] | Address_40 [Att11] [Ent30] | Hr_40 [Att11] | Pre_40 [Att13] [Ent39] | Blockquote_40 [Att14] [Ent10] | Ins_40 [Att15] [Ent40] | Del_40 [Att15] [Ent40] | A_40 [Att16] [Ent4] | Span_40 [Att11] [Ent30] | Bdo_40 [Att11] [Ent30] | Br_40 [Att19] | Em_40 [Att11] [Ent30] | Strong_40 [Att11] [Ent30] | Dfn_40 [Att11] [Ent30] | Code_40 [Att11] [Ent30] | Samp_40 [Att11] [Ent30] | Kbd_40 [Att11] [Ent30] | Var_40 [Att11] [Ent30] | Cite_40 [Att11] [Ent30] | Abbr_40 [Att11] [Ent30] | Acronym_40 [Att11] [Ent30] | Q_40 [Att14] [Ent30] | Sub_40 [Att11] [Ent30] | Sup_40 [Att11] [Ent30] | Tt_40 [Att11] [Ent30] | I_40 [Att11] [Ent30] | B_40 [Att11] [Ent30] | Big_40 [Att11] [Ent30] | Small_40 [Att11] [Ent30] | Object_40 [Att20] [Ent44] | Img_40 [Att22] | Map_40 [Att25] [Ent42] | Label_40 [Att30] [Ent31] | Input_40 [Att31] | Select_40 [Att32] [Ent27] | Textarea_40 [Att36] [Ent2] | Fieldset_40 [Att11] [Ent46] | Button_40 [Att40] [Ent29] | Table_40 [Att41] [Ent13] | PCDATA_40 [Att0] B.ByteString deriving (Show) data Ent41 = Script_41 [Att10] [Ent2] | Noscript_41 [Att11] [Ent10] | Div_41 [Att11] [Ent11] | P_41 [Att11] [Ent4] | H1_41 [Att11] [Ent4] | H2_41 [Att11] [Ent4] | H3_41 [Att11] [Ent4] | H4_41 [Att11] [Ent4] | H5_41 [Att11] [Ent4] | H6_41 [Att11] [Ent4] | Ul_41 [Att11] [Ent7] | Ol_41 [Att11] [Ent7] | Dl_41 [Att11] [Ent8] | Address_41 [Att11] [Ent4] | Hr_41 [Att11] | Pre_41 [Att13] [Ent9] | Blockquote_41 [Att14] [Ent10] | Ins_41 [Att15] [Ent11] | Del_41 [Att15] [Ent11] | Span_41 [Att11] [Ent4] | Bdo_41 [Att11] [Ent4] | Br_41 [Att19] | Em_41 [Att11] [Ent4] | Strong_41 [Att11] [Ent4] | Dfn_41 [Att11] [Ent4] | Code_41 [Att11] [Ent4] | Samp_41 [Att11] [Ent4] | Kbd_41 [Att11] [Ent4] | Var_41 [Att11] [Ent4] | Cite_41 [Att11] [Ent4] | Abbr_41 [Att11] [Ent4] | Acronym_41 [Att11] [Ent4] | Q_41 [Att14] [Ent4] | Sub_41 [Att11] [Ent4] | Sup_41 [Att11] [Ent4] | Tt_41 [Att11] [Ent4] | I_41 [Att11] [Ent4] | B_41 [Att11] [Ent4] | Big_41 [Att11] [Ent4] | Small_41 [Att11] [Ent4] | Object_41 [Att20] [Ent41] | Param_41 [Att21] | Img_41 [Att22] | Map_41 [Att25] [Ent42] | Label_41 [Att30] [Ent20] | Input_41 [Att31] | Select_41 [Att32] [Ent27] | Textarea_41 [Att36] [Ent2] | Fieldset_41 [Att11] [Ent12] | Button_41 [Att40] [Ent29] | Table_41 [Att41] [Ent13] | PCDATA_41 [Att0] B.ByteString deriving (Show) data Ent42 = Script_42 [Att10] [Ent2] | Noscript_42 [Att11] [Ent10] | Div_42 [Att11] [Ent11] | P_42 [Att11] [Ent4] | H1_42 [Att11] [Ent4] | H2_42 [Att11] [Ent4] | H3_42 [Att11] [Ent4] | H4_42 [Att11] [Ent4] | H5_42 [Att11] [Ent4] | H6_42 [Att11] [Ent4] | Ul_42 [Att11] [Ent7] | Ol_42 [Att11] [Ent7] | Dl_42 [Att11] [Ent8] | Address_42 [Att11] [Ent4] | Hr_42 [Att11] | Pre_42 [Att13] [Ent9] | Blockquote_42 [Att14] [Ent10] | Ins_42 [Att15] [Ent11] | Del_42 [Att15] [Ent11] | Area_42 [Att27] | Fieldset_42 [Att11] [Ent12] | Table_42 [Att41] [Ent13] deriving (Show) data Ent43 = Script_43 [Att10] [Ent2] | Noscript_43 [Att11] [Ent10] | Div_43 [Att11] [Ent23] | P_43 [Att11] [Ent20] | H1_43 [Att11] [Ent20] | H2_43 [Att11] [Ent20] | H3_43 [Att11] [Ent20] | H4_43 [Att11] [Ent20] | H5_43 [Att11] [Ent20] | H6_43 [Att11] [Ent20] | Ul_43 [Att11] [Ent7] | Ol_43 [Att11] [Ent7] | Dl_43 [Att11] [Ent8] | Address_43 [Att11] [Ent20] | Hr_43 [Att11] | Pre_43 [Att13] [Ent22] | Blockquote_43 [Att14] [Ent10] | Ins_43 [Att15] [Ent23] | Del_43 [Att15] [Ent23] | Span_43 [Att11] [Ent20] | Bdo_43 [Att11] [Ent20] | Br_43 [Att19] | Em_43 [Att11] [Ent20] | Strong_43 [Att11] [Ent20] | Dfn_43 [Att11] [Ent20] | Code_43 [Att11] [Ent20] | Samp_43 [Att11] [Ent20] | Kbd_43 [Att11] [Ent20] | Var_43 [Att11] [Ent20] | Cite_43 [Att11] [Ent20] | Abbr_43 [Att11] [Ent20] | Acronym_43 [Att11] [Ent20] | Q_43 [Att14] [Ent20] | Sub_43 [Att11] [Ent20] | Sup_43 [Att11] [Ent20] | Tt_43 [Att11] [Ent20] | I_43 [Att11] [Ent20] | B_43 [Att11] [Ent20] | Big_43 [Att11] [Ent20] | Small_43 [Att11] [Ent20] | Object_43 [Att20] [Ent43] | Param_43 [Att21] | Img_43 [Att22] | Map_43 [Att25] [Ent42] | Input_43 [Att31] | Select_43 [Att32] [Ent27] | Textarea_43 [Att36] [Ent2] | Fieldset_43 [Att11] [Ent24] | Button_43 [Att40] [Ent29] | Table_43 [Att41] [Ent13] | PCDATA_43 [Att0] B.ByteString deriving (Show) data Ent44 = Script_44 [Att10] [Ent2] | Noscript_44 [Att11] [Ent10] | Div_44 [Att11] [Ent40] | P_44 [Att11] [Ent30] | H1_44 [Att11] [Ent30] | H2_44 [Att11] [Ent30] | H3_44 [Att11] [Ent30] | H4_44 [Att11] [Ent30] | H5_44 [Att11] [Ent30] | H6_44 [Att11] [Ent30] | Ul_44 [Att11] [Ent7] | Ol_44 [Att11] [Ent7] | Dl_44 [Att11] [Ent8] | Address_44 [Att11] [Ent30] | Hr_44 [Att11] | Pre_44 [Att13] [Ent39] | Blockquote_44 [Att14] [Ent10] | Ins_44 [Att15] [Ent40] | Del_44 [Att15] [Ent40] | A_44 [Att16] [Ent4] | Span_44 [Att11] [Ent30] | Bdo_44 [Att11] [Ent30] | Br_44 [Att19] | Em_44 [Att11] [Ent30] | Strong_44 [Att11] [Ent30] | Dfn_44 [Att11] [Ent30] | Code_44 [Att11] [Ent30] | Samp_44 [Att11] [Ent30] | Kbd_44 [Att11] [Ent30] | Var_44 [Att11] [Ent30] | Cite_44 [Att11] [Ent30] | Abbr_44 [Att11] [Ent30] | Acronym_44 [Att11] [Ent30] | Q_44 [Att14] [Ent30] | Sub_44 [Att11] [Ent30] | Sup_44 [Att11] [Ent30] | Tt_44 [Att11] [Ent30] | I_44 [Att11] [Ent30] | B_44 [Att11] [Ent30] | Big_44 [Att11] [Ent30] | Small_44 [Att11] [Ent30] | Object_44 [Att20] [Ent44] | Param_44 [Att21] | Img_44 [Att22] | Map_44 [Att25] [Ent42] | Label_44 [Att30] [Ent31] | Input_44 [Att31] | Select_44 [Att32] [Ent27] | Textarea_44 [Att36] [Ent2] | Fieldset_44 [Att11] [Ent46] | Button_44 [Att40] [Ent29] | Table_44 [Att41] [Ent13] | PCDATA_44 [Att0] B.ByteString deriving (Show) data Ent45 = Script_45 [Att10] [Ent2] | Noscript_45 [Att11] [Ent10] | Div_45 [Att11] [Ent34] | P_45 [Att11] [Ent31] | H1_45 [Att11] [Ent31] | H2_45 [Att11] [Ent31] | H3_45 [Att11] [Ent31] | H4_45 [Att11] [Ent31] | H5_45 [Att11] [Ent31] | H6_45 [Att11] [Ent31] | Ul_45 [Att11] [Ent7] | Ol_45 [Att11] [Ent7] | Dl_45 [Att11] [Ent8] | Address_45 [Att11] [Ent31] | Hr_45 [Att11] | Pre_45 [Att13] [Ent33] | Blockquote_45 [Att14] [Ent10] | Ins_45 [Att15] [Ent34] | Del_45 [Att15] [Ent34] | A_45 [Att16] [Ent20] | Span_45 [Att11] [Ent31] | Bdo_45 [Att11] [Ent31] | Br_45 [Att19] | Em_45 [Att11] [Ent31] | Strong_45 [Att11] [Ent31] | Dfn_45 [Att11] [Ent31] | Code_45 [Att11] [Ent31] | Samp_45 [Att11] [Ent31] | Kbd_45 [Att11] [Ent31] | Var_45 [Att11] [Ent31] | Cite_45 [Att11] [Ent31] | Abbr_45 [Att11] [Ent31] | Acronym_45 [Att11] [Ent31] | Q_45 [Att14] [Ent31] | Sub_45 [Att11] [Ent31] | Sup_45 [Att11] [Ent31] | Tt_45 [Att11] [Ent31] | I_45 [Att11] [Ent31] | B_45 [Att11] [Ent31] | Big_45 [Att11] [Ent31] | Small_45 [Att11] [Ent31] | Object_45 [Att20] [Ent45] | Param_45 [Att21] | Img_45 [Att22] | Map_45 [Att25] [Ent42] | Input_45 [Att31] | Select_45 [Att32] [Ent27] | Textarea_45 [Att36] [Ent2] | Fieldset_45 [Att11] [Ent35] | Button_45 [Att40] [Ent29] | Table_45 [Att41] [Ent13] | PCDATA_45 [Att0] B.ByteString deriving (Show) data Ent46 = Script_46 [Att10] [Ent2] | Noscript_46 [Att11] [Ent10] | Div_46 [Att11] [Ent40] | P_46 [Att11] [Ent30] | H1_46 [Att11] [Ent30] | H2_46 [Att11] [Ent30] | H3_46 [Att11] [Ent30] | H4_46 [Att11] [Ent30] | H5_46 [Att11] [Ent30] | H6_46 [Att11] [Ent30] | Ul_46 [Att11] [Ent7] | Ol_46 [Att11] [Ent7] | Dl_46 [Att11] [Ent8] | Address_46 [Att11] [Ent30] | Hr_46 [Att11] | Pre_46 [Att13] [Ent39] | Blockquote_46 [Att14] [Ent10] | Ins_46 [Att15] [Ent40] | Del_46 [Att15] [Ent40] | A_46 [Att16] [Ent4] | Span_46 [Att11] [Ent30] | Bdo_46 [Att11] [Ent30] | Br_46 [Att19] | Em_46 [Att11] [Ent30] | Strong_46 [Att11] [Ent30] | Dfn_46 [Att11] [Ent30] | Code_46 [Att11] [Ent30] | Samp_46 [Att11] [Ent30] | Kbd_46 [Att11] [Ent30] | Var_46 [Att11] [Ent30] | Cite_46 [Att11] [Ent30] | Abbr_46 [Att11] [Ent30] | Acronym_46 [Att11] [Ent30] | Q_46 [Att14] [Ent30] | Sub_46 [Att11] [Ent30] | Sup_46 [Att11] [Ent30] | Tt_46 [Att11] [Ent30] | I_46 [Att11] [Ent30] | B_46 [Att11] [Ent30] | Big_46 [Att11] [Ent30] | Small_46 [Att11] [Ent30] | Object_46 [Att20] [Ent44] | Img_46 [Att22] | Map_46 [Att25] [Ent42] | Label_46 [Att30] [Ent31] | Input_46 [Att31] | Select_46 [Att32] [Ent27] | Textarea_46 [Att36] [Ent2] | Fieldset_46 [Att11] [Ent46] | Legend_46 [Att39] [Ent30] | Button_46 [Att40] [Ent29] | Table_46 [Att41] [Ent13] | PCDATA_46 [Att0] B.ByteString deriving (Show) data Ent47 = Script_47 [Att10] [Ent2] | Noscript_47 [Att11] [Ent6] | Div_47 [Att11] [Ent38] | P_47 [Att11] [Ent30] | H1_47 [Att11] [Ent30] | H2_47 [Att11] [Ent30] | H3_47 [Att11] [Ent30] | H4_47 [Att11] [Ent30] | H5_47 [Att11] [Ent30] | H6_47 [Att11] [Ent30] | Ul_47 [Att11] [Ent7] | Ol_47 [Att11] [Ent7] | Dl_47 [Att11] [Ent8] | Address_47 [Att11] [Ent30] | Hr_47 [Att11] | Pre_47 [Att13] [Ent39] | Blockquote_47 [Att14] [Ent6] | Ins_47 [Att15] [Ent38] | Del_47 [Att15] [Ent38] | A_47 [Att16] [Ent4] | Span_47 [Att11] [Ent30] | Bdo_47 [Att11] [Ent30] | Br_47 [Att19] | Em_47 [Att11] [Ent30] | Strong_47 [Att11] [Ent30] | Dfn_47 [Att11] [Ent30] | Code_47 [Att11] [Ent30] | Samp_47 [Att11] [Ent30] | Kbd_47 [Att11] [Ent30] | Var_47 [Att11] [Ent30] | Cite_47 [Att11] [Ent30] | Abbr_47 [Att11] [Ent30] | Acronym_47 [Att11] [Ent30] | Q_47 [Att14] [Ent30] | Sub_47 [Att11] [Ent30] | Sup_47 [Att11] [Ent30] | Tt_47 [Att11] [Ent30] | I_47 [Att11] [Ent30] | B_47 [Att11] [Ent30] | Big_47 [Att11] [Ent30] | Small_47 [Att11] [Ent30] | Object_47 [Att20] [Ent3] | Img_47 [Att22] | Map_47 [Att25] [Ent19] | Form_47 [Att28] [Ent10] | Label_47 [Att30] [Ent31] | Input_47 [Att31] | Select_47 [Att32] [Ent27] | Textarea_47 [Att36] [Ent2] | Fieldset_47 [Att11] [Ent47] | Legend_47 [Att39] [Ent30] | Button_47 [Att40] [Ent29] | Table_47 [Att41] [Ent13] | PCDATA_47 [Att0] B.ByteString 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 Ent2 where _script = Script_4 [] script_ = Script_4 instance C_Script Ent5 Ent2 where _script = Script_5 [] script_ = Script_5 instance C_Script Ent6 Ent2 where _script = Script_6 [] script_ = Script_6 instance C_Script Ent9 Ent2 where _script = Script_9 [] script_ = Script_9 instance C_Script Ent10 Ent2 where _script = Script_10 [] script_ = Script_10 instance C_Script Ent11 Ent2 where _script = Script_11 [] script_ = Script_11 instance C_Script Ent12 Ent2 where _script = Script_12 [] script_ = Script_12 instance C_Script Ent17 Ent2 where _script = Script_17 [] script_ = Script_17 instance C_Script Ent18 Ent2 where _script = Script_18 [] script_ = Script_18 instance C_Script Ent19 Ent2 where _script = Script_19 [] script_ = Script_19 instance C_Script Ent20 Ent2 where _script = Script_20 [] script_ = Script_20 instance C_Script Ent21 Ent2 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 Ent24 Ent2 where _script = Script_24 [] script_ = Script_24 instance C_Script Ent25 Ent2 where _script = Script_25 [] script_ = Script_25 instance C_Script Ent26 Ent2 where _script = Script_26 [] script_ = Script_26 instance C_Script Ent29 Ent2 where _script = Script_29 [] script_ = Script_29 instance C_Script Ent30 Ent2 where _script = Script_30 [] script_ = Script_30 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 instance C_Script Ent34 Ent2 where _script = Script_34 [] script_ = Script_34 instance C_Script Ent35 Ent2 where _script = Script_35 [] script_ = Script_35 instance C_Script Ent36 Ent2 where _script = Script_36 [] script_ = Script_36 instance C_Script Ent37 Ent2 where _script = Script_37 [] script_ = Script_37 instance C_Script Ent38 Ent2 where _script = Script_38 [] script_ = Script_38 instance C_Script Ent39 Ent2 where _script = Script_39 [] script_ = Script_39 instance C_Script Ent40 Ent2 where _script = Script_40 [] script_ = Script_40 instance C_Script Ent41 Ent2 where _script = Script_41 [] script_ = Script_41 instance C_Script Ent42 Ent2 where _script = Script_42 [] script_ = Script_42 instance C_Script Ent43 Ent2 where _script = Script_43 [] script_ = Script_43 instance C_Script Ent44 Ent2 where _script = Script_44 [] script_ = Script_44 instance C_Script Ent45 Ent2 where _script = Script_45 [] script_ = Script_45 instance C_Script Ent46 Ent2 where _script = Script_46 [] script_ = Script_46 instance C_Script Ent47 Ent2 where _script = Script_47 [] script_ = Script_47 class C_Noscript a b | a -> b where _noscript :: [b] -> a noscript_ :: [Att11] -> [b] -> a instance C_Noscript Ent3 Ent6 where _noscript = Noscript_3 [] noscript_ = Noscript_3 instance C_Noscript Ent5 Ent6 where _noscript = Noscript_5 [] noscript_ = Noscript_5 instance C_Noscript Ent6 Ent6 where _noscript = Noscript_6 [] noscript_ = Noscript_6 instance C_Noscript Ent10 Ent10 where _noscript = Noscript_10 [] noscript_ = Noscript_10 instance C_Noscript Ent11 Ent10 where _noscript = Noscript_11 [] noscript_ = Noscript_11 instance C_Noscript Ent12 Ent10 where _noscript = Noscript_12 [] noscript_ = Noscript_12 instance C_Noscript Ent17 Ent6 where _noscript = Noscript_17 [] noscript_ = Noscript_17 instance C_Noscript Ent18 Ent6 where _noscript = Noscript_18 [] noscript_ = Noscript_18 instance C_Noscript Ent19 Ent6 where _noscript = Noscript_19 [] noscript_ = Noscript_19 instance C_Noscript Ent21 Ent6 where _noscript = Noscript_21 [] noscript_ = Noscript_21 instance C_Noscript Ent23 Ent10 where _noscript = Noscript_23 [] noscript_ = Noscript_23 instance C_Noscript Ent24 Ent10 where _noscript = Noscript_24 [] noscript_ = Noscript_24 instance C_Noscript Ent25 Ent6 where _noscript = Noscript_25 [] noscript_ = Noscript_25 instance C_Noscript Ent26 Ent6 where _noscript = Noscript_26 [] noscript_ = Noscript_26 instance C_Noscript Ent29 Ent6 where _noscript = Noscript_29 [] noscript_ = Noscript_29 instance C_Noscript Ent32 Ent6 where _noscript = Noscript_32 [] noscript_ = Noscript_32 instance C_Noscript Ent34 Ent10 where _noscript = Noscript_34 [] noscript_ = Noscript_34 instance C_Noscript Ent35 Ent10 where _noscript = Noscript_35 [] noscript_ = Noscript_35 instance C_Noscript Ent36 Ent6 where _noscript = Noscript_36 [] noscript_ = Noscript_36 instance C_Noscript Ent37 Ent6 where _noscript = Noscript_37 [] noscript_ = Noscript_37 instance C_Noscript Ent38 Ent6 where _noscript = Noscript_38 [] noscript_ = Noscript_38 instance C_Noscript Ent40 Ent10 where _noscript = Noscript_40 [] noscript_ = Noscript_40 instance C_Noscript Ent41 Ent10 where _noscript = Noscript_41 [] noscript_ = Noscript_41 instance C_Noscript Ent42 Ent10 where _noscript = Noscript_42 [] noscript_ = Noscript_42 instance C_Noscript Ent43 Ent10 where _noscript = Noscript_43 [] noscript_ = Noscript_43 instance C_Noscript Ent44 Ent10 where _noscript = Noscript_44 [] noscript_ = Noscript_44 instance C_Noscript Ent45 Ent10 where _noscript = Noscript_45 [] noscript_ = Noscript_45 instance C_Noscript Ent46 Ent10 where _noscript = Noscript_46 [] noscript_ = Noscript_46 instance C_Noscript Ent47 Ent6 where _noscript = Noscript_47 [] noscript_ = Noscript_47 class C_Body a b | a -> b where _body :: [b] -> a body_ :: [Att12] -> [b] -> a instance C_Body Ent0 Ent6 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 Ent38 where _div = Div_3 [] div_ = Div_3 instance C_Div Ent5 Ent5 where _div = Div_5 [] div_ = Div_5 instance C_Div Ent6 Ent5 where _div = Div_6 [] div_ = Div_6 instance C_Div Ent10 Ent11 where _div = Div_10 [] div_ = Div_10 instance C_Div Ent11 Ent11 where _div = Div_11 [] div_ = Div_11 instance C_Div Ent12 Ent11 where _div = Div_12 [] div_ = Div_12 instance C_Div Ent17 Ent5 where _div = Div_17 [] div_ = Div_17 instance C_Div Ent18 Ent5 where _div = Div_18 [] div_ = Div_18 instance C_Div Ent19 Ent5 where _div = Div_19 [] div_ = Div_19 instance C_Div Ent21 Ent21 where _div = Div_21 [] div_ = Div_21 instance C_Div Ent23 Ent23 where _div = Div_23 [] div_ = Div_23 instance C_Div Ent24 Ent23 where _div = Div_24 [] div_ = Div_24 instance C_Div Ent25 Ent21 where _div = Div_25 [] div_ = Div_25 instance C_Div Ent26 Ent21 where _div = Div_26 [] div_ = Div_26 instance C_Div Ent29 Ent21 where _div = Div_29 [] div_ = Div_29 instance C_Div Ent32 Ent32 where _div = Div_32 [] div_ = Div_32 instance C_Div Ent34 Ent34 where _div = Div_34 [] div_ = Div_34 instance C_Div Ent35 Ent34 where _div = Div_35 [] div_ = Div_35 instance C_Div Ent36 Ent32 where _div = Div_36 [] div_ = Div_36 instance C_Div Ent37 Ent32 where _div = Div_37 [] div_ = Div_37 instance C_Div Ent38 Ent38 where _div = Div_38 [] div_ = Div_38 instance C_Div Ent40 Ent40 where _div = Div_40 [] div_ = Div_40 instance C_Div Ent41 Ent11 where _div = Div_41 [] div_ = Div_41 instance C_Div Ent42 Ent11 where _div = Div_42 [] div_ = Div_42 instance C_Div Ent43 Ent23 where _div = Div_43 [] div_ = Div_43 instance C_Div Ent44 Ent40 where _div = Div_44 [] div_ = Div_44 instance C_Div Ent45 Ent34 where _div = Div_45 [] div_ = Div_45 instance C_Div Ent46 Ent40 where _div = Div_46 [] div_ = Div_46 instance C_Div Ent47 Ent38 where _div = Div_47 [] div_ = Div_47 class C_P a b | a -> b where _p :: [b] -> a p_ :: [Att11] -> [b] -> a instance C_P Ent3 Ent30 where _p = P_3 [] p_ = P_3 instance C_P Ent5 Ent4 where _p = P_5 [] p_ = P_5 instance C_P Ent6 Ent4 where _p = P_6 [] p_ = P_6 instance C_P Ent10 Ent4 where _p = P_10 [] p_ = P_10 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 Ent19 Ent4 where _p = P_19 [] p_ = P_19 instance C_P Ent21 Ent20 where _p = P_21 [] p_ = P_21 instance C_P Ent23 Ent20 where _p = P_23 [] p_ = P_23 instance C_P Ent24 Ent20 where _p = P_24 [] p_ = P_24 instance C_P Ent25 Ent20 where _p = P_25 [] p_ = P_25 instance C_P Ent26 Ent20 where _p = P_26 [] p_ = P_26 instance C_P Ent29 Ent20 where _p = P_29 [] p_ = P_29 instance C_P Ent32 Ent31 where _p = P_32 [] p_ = P_32 instance C_P Ent34 Ent31 where _p = P_34 [] p_ = P_34 instance C_P Ent35 Ent31 where _p = P_35 [] p_ = P_35 instance C_P Ent36 Ent31 where _p = P_36 [] p_ = P_36 instance C_P Ent37 Ent31 where _p = P_37 [] p_ = P_37 instance C_P Ent38 Ent30 where _p = P_38 [] p_ = P_38 instance C_P Ent40 Ent30 where _p = P_40 [] p_ = P_40 instance C_P Ent41 Ent4 where _p = P_41 [] p_ = P_41 instance C_P Ent42 Ent4 where _p = P_42 [] p_ = P_42 instance C_P Ent43 Ent20 where _p = P_43 [] p_ = P_43 instance C_P Ent44 Ent30 where _p = P_44 [] p_ = P_44 instance C_P Ent45 Ent31 where _p = P_45 [] p_ = P_45 instance C_P Ent46 Ent30 where _p = P_46 [] p_ = P_46 instance C_P Ent47 Ent30 where _p = P_47 [] p_ = P_47 class C_H1 a b | a -> b where _h1 :: [b] -> a h1_ :: [Att11] -> [b] -> a instance C_H1 Ent3 Ent30 where _h1 = H1_3 [] h1_ = H1_3 instance C_H1 Ent5 Ent4 where _h1 = H1_5 [] h1_ = H1_5 instance C_H1 Ent6 Ent4 where _h1 = H1_6 [] h1_ = H1_6 instance C_H1 Ent10 Ent4 where _h1 = H1_10 [] h1_ = H1_10 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 Ent19 Ent4 where _h1 = H1_19 [] h1_ = H1_19 instance C_H1 Ent21 Ent20 where _h1 = H1_21 [] h1_ = H1_21 instance C_H1 Ent23 Ent20 where _h1 = H1_23 [] h1_ = H1_23 instance C_H1 Ent24 Ent20 where _h1 = H1_24 [] h1_ = H1_24 instance C_H1 Ent25 Ent20 where _h1 = H1_25 [] h1_ = H1_25 instance C_H1 Ent26 Ent20 where _h1 = H1_26 [] h1_ = H1_26 instance C_H1 Ent29 Ent20 where _h1 = H1_29 [] h1_ = H1_29 instance C_H1 Ent32 Ent31 where _h1 = H1_32 [] h1_ = H1_32 instance C_H1 Ent34 Ent31 where _h1 = H1_34 [] h1_ = H1_34 instance C_H1 Ent35 Ent31 where _h1 = H1_35 [] h1_ = H1_35 instance C_H1 Ent36 Ent31 where _h1 = H1_36 [] h1_ = H1_36 instance C_H1 Ent37 Ent31 where _h1 = H1_37 [] h1_ = H1_37 instance C_H1 Ent38 Ent30 where _h1 = H1_38 [] h1_ = H1_38 instance C_H1 Ent40 Ent30 where _h1 = H1_40 [] h1_ = H1_40 instance C_H1 Ent41 Ent4 where _h1 = H1_41 [] h1_ = H1_41 instance C_H1 Ent42 Ent4 where _h1 = H1_42 [] h1_ = H1_42 instance C_H1 Ent43 Ent20 where _h1 = H1_43 [] h1_ = H1_43 instance C_H1 Ent44 Ent30 where _h1 = H1_44 [] h1_ = H1_44 instance C_H1 Ent45 Ent31 where _h1 = H1_45 [] h1_ = H1_45 instance C_H1 Ent46 Ent30 where _h1 = H1_46 [] h1_ = H1_46 instance C_H1 Ent47 Ent30 where _h1 = H1_47 [] h1_ = H1_47 class C_H2 a b | a -> b where _h2 :: [b] -> a h2_ :: [Att11] -> [b] -> a instance C_H2 Ent3 Ent30 where _h2 = H2_3 [] h2_ = H2_3 instance C_H2 Ent5 Ent4 where _h2 = H2_5 [] h2_ = H2_5 instance C_H2 Ent6 Ent4 where _h2 = H2_6 [] h2_ = H2_6 instance C_H2 Ent10 Ent4 where _h2 = H2_10 [] h2_ = H2_10 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 Ent19 Ent4 where _h2 = H2_19 [] h2_ = H2_19 instance C_H2 Ent21 Ent20 where _h2 = H2_21 [] h2_ = H2_21 instance C_H2 Ent23 Ent20 where _h2 = H2_23 [] h2_ = H2_23 instance C_H2 Ent24 Ent20 where _h2 = H2_24 [] h2_ = H2_24 instance C_H2 Ent25 Ent20 where _h2 = H2_25 [] h2_ = H2_25 instance C_H2 Ent26 Ent20 where _h2 = H2_26 [] h2_ = H2_26 instance C_H2 Ent29 Ent20 where _h2 = H2_29 [] h2_ = H2_29 instance C_H2 Ent32 Ent31 where _h2 = H2_32 [] h2_ = H2_32 instance C_H2 Ent34 Ent31 where _h2 = H2_34 [] h2_ = H2_34 instance C_H2 Ent35 Ent31 where _h2 = H2_35 [] h2_ = H2_35 instance C_H2 Ent36 Ent31 where _h2 = H2_36 [] h2_ = H2_36 instance C_H2 Ent37 Ent31 where _h2 = H2_37 [] h2_ = H2_37 instance C_H2 Ent38 Ent30 where _h2 = H2_38 [] h2_ = H2_38 instance C_H2 Ent40 Ent30 where _h2 = H2_40 [] h2_ = H2_40 instance C_H2 Ent41 Ent4 where _h2 = H2_41 [] h2_ = H2_41 instance C_H2 Ent42 Ent4 where _h2 = H2_42 [] h2_ = H2_42 instance C_H2 Ent43 Ent20 where _h2 = H2_43 [] h2_ = H2_43 instance C_H2 Ent44 Ent30 where _h2 = H2_44 [] h2_ = H2_44 instance C_H2 Ent45 Ent31 where _h2 = H2_45 [] h2_ = H2_45 instance C_H2 Ent46 Ent30 where _h2 = H2_46 [] h2_ = H2_46 instance C_H2 Ent47 Ent30 where _h2 = H2_47 [] h2_ = H2_47 class C_H3 a b | a -> b where _h3 :: [b] -> a h3_ :: [Att11] -> [b] -> a instance C_H3 Ent3 Ent30 where _h3 = H3_3 [] h3_ = H3_3 instance C_H3 Ent5 Ent4 where _h3 = H3_5 [] h3_ = H3_5 instance C_H3 Ent6 Ent4 where _h3 = H3_6 [] h3_ = H3_6 instance C_H3 Ent10 Ent4 where _h3 = H3_10 [] h3_ = H3_10 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 Ent19 Ent4 where _h3 = H3_19 [] h3_ = H3_19 instance C_H3 Ent21 Ent20 where _h3 = H3_21 [] h3_ = H3_21 instance C_H3 Ent23 Ent20 where _h3 = H3_23 [] h3_ = H3_23 instance C_H3 Ent24 Ent20 where _h3 = H3_24 [] h3_ = H3_24 instance C_H3 Ent25 Ent20 where _h3 = H3_25 [] h3_ = H3_25 instance C_H3 Ent26 Ent20 where _h3 = H3_26 [] h3_ = H3_26 instance C_H3 Ent29 Ent20 where _h3 = H3_29 [] h3_ = H3_29 instance C_H3 Ent32 Ent31 where _h3 = H3_32 [] h3_ = H3_32 instance C_H3 Ent34 Ent31 where _h3 = H3_34 [] h3_ = H3_34 instance C_H3 Ent35 Ent31 where _h3 = H3_35 [] h3_ = H3_35 instance C_H3 Ent36 Ent31 where _h3 = H3_36 [] h3_ = H3_36 instance C_H3 Ent37 Ent31 where _h3 = H3_37 [] h3_ = H3_37 instance C_H3 Ent38 Ent30 where _h3 = H3_38 [] h3_ = H3_38 instance C_H3 Ent40 Ent30 where _h3 = H3_40 [] h3_ = H3_40 instance C_H3 Ent41 Ent4 where _h3 = H3_41 [] h3_ = H3_41 instance C_H3 Ent42 Ent4 where _h3 = H3_42 [] h3_ = H3_42 instance C_H3 Ent43 Ent20 where _h3 = H3_43 [] h3_ = H3_43 instance C_H3 Ent44 Ent30 where _h3 = H3_44 [] h3_ = H3_44 instance C_H3 Ent45 Ent31 where _h3 = H3_45 [] h3_ = H3_45 instance C_H3 Ent46 Ent30 where _h3 = H3_46 [] h3_ = H3_46 instance C_H3 Ent47 Ent30 where _h3 = H3_47 [] h3_ = H3_47 class C_H4 a b | a -> b where _h4 :: [b] -> a h4_ :: [Att11] -> [b] -> a instance C_H4 Ent3 Ent30 where _h4 = H4_3 [] h4_ = H4_3 instance C_H4 Ent5 Ent4 where _h4 = H4_5 [] h4_ = H4_5 instance C_H4 Ent6 Ent4 where _h4 = H4_6 [] h4_ = H4_6 instance C_H4 Ent10 Ent4 where _h4 = H4_10 [] h4_ = H4_10 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 Ent19 Ent4 where _h4 = H4_19 [] h4_ = H4_19 instance C_H4 Ent21 Ent20 where _h4 = H4_21 [] h4_ = H4_21 instance C_H4 Ent23 Ent20 where _h4 = H4_23 [] h4_ = H4_23 instance C_H4 Ent24 Ent20 where _h4 = H4_24 [] h4_ = H4_24 instance C_H4 Ent25 Ent20 where _h4 = H4_25 [] h4_ = H4_25 instance C_H4 Ent26 Ent20 where _h4 = H4_26 [] h4_ = H4_26 instance C_H4 Ent29 Ent20 where _h4 = H4_29 [] h4_ = H4_29 instance C_H4 Ent32 Ent31 where _h4 = H4_32 [] h4_ = H4_32 instance C_H4 Ent34 Ent31 where _h4 = H4_34 [] h4_ = H4_34 instance C_H4 Ent35 Ent31 where _h4 = H4_35 [] h4_ = H4_35 instance C_H4 Ent36 Ent31 where _h4 = H4_36 [] h4_ = H4_36 instance C_H4 Ent37 Ent31 where _h4 = H4_37 [] h4_ = H4_37 instance C_H4 Ent38 Ent30 where _h4 = H4_38 [] h4_ = H4_38 instance C_H4 Ent40 Ent30 where _h4 = H4_40 [] h4_ = H4_40 instance C_H4 Ent41 Ent4 where _h4 = H4_41 [] h4_ = H4_41 instance C_H4 Ent42 Ent4 where _h4 = H4_42 [] h4_ = H4_42 instance C_H4 Ent43 Ent20 where _h4 = H4_43 [] h4_ = H4_43 instance C_H4 Ent44 Ent30 where _h4 = H4_44 [] h4_ = H4_44 instance C_H4 Ent45 Ent31 where _h4 = H4_45 [] h4_ = H4_45 instance C_H4 Ent46 Ent30 where _h4 = H4_46 [] h4_ = H4_46 instance C_H4 Ent47 Ent30 where _h4 = H4_47 [] h4_ = H4_47 class C_H5 a b | a -> b where _h5 :: [b] -> a h5_ :: [Att11] -> [b] -> a instance C_H5 Ent3 Ent30 where _h5 = H5_3 [] h5_ = H5_3 instance C_H5 Ent5 Ent4 where _h5 = H5_5 [] h5_ = H5_5 instance C_H5 Ent6 Ent4 where _h5 = H5_6 [] h5_ = H5_6 instance C_H5 Ent10 Ent4 where _h5 = H5_10 [] h5_ = H5_10 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 Ent19 Ent4 where _h5 = H5_19 [] h5_ = H5_19 instance C_H5 Ent21 Ent20 where _h5 = H5_21 [] h5_ = H5_21 instance C_H5 Ent23 Ent20 where _h5 = H5_23 [] h5_ = H5_23 instance C_H5 Ent24 Ent20 where _h5 = H5_24 [] h5_ = H5_24 instance C_H5 Ent25 Ent20 where _h5 = H5_25 [] h5_ = H5_25 instance C_H5 Ent26 Ent20 where _h5 = H5_26 [] h5_ = H5_26 instance C_H5 Ent29 Ent20 where _h5 = H5_29 [] h5_ = H5_29 instance C_H5 Ent32 Ent31 where _h5 = H5_32 [] h5_ = H5_32 instance C_H5 Ent34 Ent31 where _h5 = H5_34 [] h5_ = H5_34 instance C_H5 Ent35 Ent31 where _h5 = H5_35 [] h5_ = H5_35 instance C_H5 Ent36 Ent31 where _h5 = H5_36 [] h5_ = H5_36 instance C_H5 Ent37 Ent31 where _h5 = H5_37 [] h5_ = H5_37 instance C_H5 Ent38 Ent30 where _h5 = H5_38 [] h5_ = H5_38 instance C_H5 Ent40 Ent30 where _h5 = H5_40 [] h5_ = H5_40 instance C_H5 Ent41 Ent4 where _h5 = H5_41 [] h5_ = H5_41 instance C_H5 Ent42 Ent4 where _h5 = H5_42 [] h5_ = H5_42 instance C_H5 Ent43 Ent20 where _h5 = H5_43 [] h5_ = H5_43 instance C_H5 Ent44 Ent30 where _h5 = H5_44 [] h5_ = H5_44 instance C_H5 Ent45 Ent31 where _h5 = H5_45 [] h5_ = H5_45 instance C_H5 Ent46 Ent30 where _h5 = H5_46 [] h5_ = H5_46 instance C_H5 Ent47 Ent30 where _h5 = H5_47 [] h5_ = H5_47 class C_H6 a b | a -> b where _h6 :: [b] -> a h6_ :: [Att11] -> [b] -> a instance C_H6 Ent3 Ent30 where _h6 = H6_3 [] h6_ = H6_3 instance C_H6 Ent5 Ent4 where _h6 = H6_5 [] h6_ = H6_5 instance C_H6 Ent6 Ent4 where _h6 = H6_6 [] h6_ = H6_6 instance C_H6 Ent10 Ent4 where _h6 = H6_10 [] h6_ = H6_10 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 Ent19 Ent4 where _h6 = H6_19 [] h6_ = H6_19 instance C_H6 Ent21 Ent20 where _h6 = H6_21 [] h6_ = H6_21 instance C_H6 Ent23 Ent20 where _h6 = H6_23 [] h6_ = H6_23 instance C_H6 Ent24 Ent20 where _h6 = H6_24 [] h6_ = H6_24 instance C_H6 Ent25 Ent20 where _h6 = H6_25 [] h6_ = H6_25 instance C_H6 Ent26 Ent20 where _h6 = H6_26 [] h6_ = H6_26 instance C_H6 Ent29 Ent20 where _h6 = H6_29 [] h6_ = H6_29 instance C_H6 Ent32 Ent31 where _h6 = H6_32 [] h6_ = H6_32 instance C_H6 Ent34 Ent31 where _h6 = H6_34 [] h6_ = H6_34 instance C_H6 Ent35 Ent31 where _h6 = H6_35 [] h6_ = H6_35 instance C_H6 Ent36 Ent31 where _h6 = H6_36 [] h6_ = H6_36 instance C_H6 Ent37 Ent31 where _h6 = H6_37 [] h6_ = H6_37 instance C_H6 Ent38 Ent30 where _h6 = H6_38 [] h6_ = H6_38 instance C_H6 Ent40 Ent30 where _h6 = H6_40 [] h6_ = H6_40 instance C_H6 Ent41 Ent4 where _h6 = H6_41 [] h6_ = H6_41 instance C_H6 Ent42 Ent4 where _h6 = H6_42 [] h6_ = H6_42 instance C_H6 Ent43 Ent20 where _h6 = H6_43 [] h6_ = H6_43 instance C_H6 Ent44 Ent30 where _h6 = H6_44 [] h6_ = H6_44 instance C_H6 Ent45 Ent31 where _h6 = H6_45 [] h6_ = H6_45 instance C_H6 Ent46 Ent30 where _h6 = H6_46 [] h6_ = H6_46 instance C_H6 Ent47 Ent30 where _h6 = H6_47 [] h6_ = H6_47 class C_Ul a b | a -> b where _ul :: [b] -> a ul_ :: [Att11] -> [b] -> a instance C_Ul Ent3 Ent7 where _ul = Ul_3 [] ul_ = Ul_3 instance C_Ul Ent5 Ent7 where _ul = Ul_5 [] ul_ = Ul_5 instance C_Ul Ent6 Ent7 where _ul = Ul_6 [] ul_ = Ul_6 instance C_Ul Ent10 Ent7 where _ul = Ul_10 [] ul_ = Ul_10 instance C_Ul Ent11 Ent7 where _ul = Ul_11 [] ul_ = Ul_11 instance C_Ul Ent12 Ent7 where _ul = Ul_12 [] ul_ = Ul_12 instance C_Ul Ent17 Ent7 where _ul = Ul_17 [] ul_ = Ul_17 instance C_Ul Ent18 Ent7 where _ul = Ul_18 [] ul_ = Ul_18 instance C_Ul Ent19 Ent7 where _ul = Ul_19 [] ul_ = Ul_19 instance C_Ul Ent21 Ent7 where _ul = Ul_21 [] ul_ = Ul_21 instance C_Ul Ent23 Ent7 where _ul = Ul_23 [] ul_ = Ul_23 instance C_Ul Ent24 Ent7 where _ul = Ul_24 [] ul_ = Ul_24 instance C_Ul Ent25 Ent7 where _ul = Ul_25 [] ul_ = Ul_25 instance C_Ul Ent26 Ent7 where _ul = Ul_26 [] ul_ = Ul_26 instance C_Ul Ent29 Ent7 where _ul = Ul_29 [] ul_ = Ul_29 instance C_Ul Ent32 Ent7 where _ul = Ul_32 [] ul_ = Ul_32 instance C_Ul Ent34 Ent7 where _ul = Ul_34 [] ul_ = Ul_34 instance C_Ul Ent35 Ent7 where _ul = Ul_35 [] ul_ = Ul_35 instance C_Ul Ent36 Ent7 where _ul = Ul_36 [] ul_ = Ul_36 instance C_Ul Ent37 Ent7 where _ul = Ul_37 [] ul_ = Ul_37 instance C_Ul Ent38 Ent7 where _ul = Ul_38 [] ul_ = Ul_38 instance C_Ul Ent40 Ent7 where _ul = Ul_40 [] ul_ = Ul_40 instance C_Ul Ent41 Ent7 where _ul = Ul_41 [] ul_ = Ul_41 instance C_Ul Ent42 Ent7 where _ul = Ul_42 [] ul_ = Ul_42 instance C_Ul Ent43 Ent7 where _ul = Ul_43 [] ul_ = Ul_43 instance C_Ul Ent44 Ent7 where _ul = Ul_44 [] ul_ = Ul_44 instance C_Ul Ent45 Ent7 where _ul = Ul_45 [] ul_ = Ul_45 instance C_Ul Ent46 Ent7 where _ul = Ul_46 [] ul_ = Ul_46 instance C_Ul Ent47 Ent7 where _ul = Ul_47 [] ul_ = Ul_47 class C_Ol a b | a -> b where _ol :: [b] -> a ol_ :: [Att11] -> [b] -> a instance C_Ol Ent3 Ent7 where _ol = Ol_3 [] ol_ = Ol_3 instance C_Ol Ent5 Ent7 where _ol = Ol_5 [] ol_ = Ol_5 instance C_Ol Ent6 Ent7 where _ol = Ol_6 [] ol_ = Ol_6 instance C_Ol Ent10 Ent7 where _ol = Ol_10 [] ol_ = Ol_10 instance C_Ol Ent11 Ent7 where _ol = Ol_11 [] ol_ = Ol_11 instance C_Ol Ent12 Ent7 where _ol = Ol_12 [] ol_ = Ol_12 instance C_Ol Ent17 Ent7 where _ol = Ol_17 [] ol_ = Ol_17 instance C_Ol Ent18 Ent7 where _ol = Ol_18 [] ol_ = Ol_18 instance C_Ol Ent19 Ent7 where _ol = Ol_19 [] ol_ = Ol_19 instance C_Ol Ent21 Ent7 where _ol = Ol_21 [] ol_ = Ol_21 instance C_Ol Ent23 Ent7 where _ol = Ol_23 [] ol_ = Ol_23 instance C_Ol Ent24 Ent7 where _ol = Ol_24 [] ol_ = Ol_24 instance C_Ol Ent25 Ent7 where _ol = Ol_25 [] ol_ = Ol_25 instance C_Ol Ent26 Ent7 where _ol = Ol_26 [] ol_ = Ol_26 instance C_Ol Ent29 Ent7 where _ol = Ol_29 [] ol_ = Ol_29 instance C_Ol Ent32 Ent7 where _ol = Ol_32 [] ol_ = Ol_32 instance C_Ol Ent34 Ent7 where _ol = Ol_34 [] ol_ = Ol_34 instance C_Ol Ent35 Ent7 where _ol = Ol_35 [] ol_ = Ol_35 instance C_Ol Ent36 Ent7 where _ol = Ol_36 [] ol_ = Ol_36 instance C_Ol Ent37 Ent7 where _ol = Ol_37 [] ol_ = Ol_37 instance C_Ol Ent38 Ent7 where _ol = Ol_38 [] ol_ = Ol_38 instance C_Ol Ent40 Ent7 where _ol = Ol_40 [] ol_ = Ol_40 instance C_Ol Ent41 Ent7 where _ol = Ol_41 [] ol_ = Ol_41 instance C_Ol Ent42 Ent7 where _ol = Ol_42 [] ol_ = Ol_42 instance C_Ol Ent43 Ent7 where _ol = Ol_43 [] ol_ = Ol_43 instance C_Ol Ent44 Ent7 where _ol = Ol_44 [] ol_ = Ol_44 instance C_Ol Ent45 Ent7 where _ol = Ol_45 [] ol_ = Ol_45 instance C_Ol Ent46 Ent7 where _ol = Ol_46 [] ol_ = Ol_46 instance C_Ol Ent47 Ent7 where _ol = Ol_47 [] ol_ = Ol_47 class C_Li a b | a -> b where _li :: [b] -> a li_ :: [Att11] -> [b] -> a instance C_Li Ent7 Ent5 where _li = Li_7 [] li_ = Li_7 class C_Dl a b | a -> b where _dl :: [b] -> a dl_ :: [Att11] -> [b] -> a instance C_Dl Ent3 Ent8 where _dl = Dl_3 [] dl_ = Dl_3 instance C_Dl Ent5 Ent8 where _dl = Dl_5 [] dl_ = Dl_5 instance C_Dl Ent6 Ent8 where _dl = Dl_6 [] dl_ = Dl_6 instance C_Dl Ent10 Ent8 where _dl = Dl_10 [] dl_ = Dl_10 instance C_Dl Ent11 Ent8 where _dl = Dl_11 [] dl_ = Dl_11 instance C_Dl Ent12 Ent8 where _dl = Dl_12 [] dl_ = Dl_12 instance C_Dl Ent17 Ent8 where _dl = Dl_17 [] dl_ = Dl_17 instance C_Dl Ent18 Ent8 where _dl = Dl_18 [] dl_ = Dl_18 instance C_Dl Ent19 Ent8 where _dl = Dl_19 [] dl_ = Dl_19 instance C_Dl Ent21 Ent8 where _dl = Dl_21 [] dl_ = Dl_21 instance C_Dl Ent23 Ent8 where _dl = Dl_23 [] dl_ = Dl_23 instance C_Dl Ent24 Ent8 where _dl = Dl_24 [] dl_ = Dl_24 instance C_Dl Ent25 Ent8 where _dl = Dl_25 [] dl_ = Dl_25 instance C_Dl Ent26 Ent8 where _dl = Dl_26 [] dl_ = Dl_26 instance C_Dl Ent29 Ent8 where _dl = Dl_29 [] dl_ = Dl_29 instance C_Dl Ent32 Ent8 where _dl = Dl_32 [] dl_ = Dl_32 instance C_Dl Ent34 Ent8 where _dl = Dl_34 [] dl_ = Dl_34 instance C_Dl Ent35 Ent8 where _dl = Dl_35 [] dl_ = Dl_35 instance C_Dl Ent36 Ent8 where _dl = Dl_36 [] dl_ = Dl_36 instance C_Dl Ent37 Ent8 where _dl = Dl_37 [] dl_ = Dl_37 instance C_Dl Ent38 Ent8 where _dl = Dl_38 [] dl_ = Dl_38 instance C_Dl Ent40 Ent8 where _dl = Dl_40 [] dl_ = Dl_40 instance C_Dl Ent41 Ent8 where _dl = Dl_41 [] dl_ = Dl_41 instance C_Dl Ent42 Ent8 where _dl = Dl_42 [] dl_ = Dl_42 instance C_Dl Ent43 Ent8 where _dl = Dl_43 [] dl_ = Dl_43 instance C_Dl Ent44 Ent8 where _dl = Dl_44 [] dl_ = Dl_44 instance C_Dl Ent45 Ent8 where _dl = Dl_45 [] dl_ = Dl_45 instance C_Dl Ent46 Ent8 where _dl = Dl_46 [] dl_ = Dl_46 instance C_Dl Ent47 Ent8 where _dl = Dl_47 [] dl_ = Dl_47 class C_Dt a b | a -> b where _dt :: [b] -> a dt_ :: [Att11] -> [b] -> a instance C_Dt Ent8 Ent4 where _dt = Dt_8 [] dt_ = Dt_8 class C_Dd a b | a -> b where _dd :: [b] -> a dd_ :: [Att11] -> [b] -> a instance C_Dd Ent8 Ent5 where _dd = Dd_8 [] dd_ = Dd_8 class C_Address a b | a -> b where _address :: [b] -> a address_ :: [Att11] -> [b] -> a instance C_Address Ent3 Ent30 where _address = Address_3 [] address_ = Address_3 instance C_Address Ent5 Ent4 where _address = Address_5 [] address_ = Address_5 instance C_Address Ent6 Ent4 where _address = Address_6 [] address_ = Address_6 instance C_Address Ent10 Ent4 where _address = Address_10 [] address_ = Address_10 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 Ent19 Ent4 where _address = Address_19 [] address_ = Address_19 instance C_Address Ent21 Ent20 where _address = Address_21 [] address_ = Address_21 instance C_Address Ent23 Ent20 where _address = Address_23 [] address_ = Address_23 instance C_Address Ent24 Ent20 where _address = Address_24 [] address_ = Address_24 instance C_Address Ent25 Ent20 where _address = Address_25 [] address_ = Address_25 instance C_Address Ent26 Ent20 where _address = Address_26 [] address_ = Address_26 instance C_Address Ent29 Ent20 where _address = Address_29 [] address_ = Address_29 instance C_Address Ent32 Ent31 where _address = Address_32 [] address_ = Address_32 instance C_Address Ent34 Ent31 where _address = Address_34 [] address_ = Address_34 instance C_Address Ent35 Ent31 where _address = Address_35 [] address_ = Address_35 instance C_Address Ent36 Ent31 where _address = Address_36 [] address_ = Address_36 instance C_Address Ent37 Ent31 where _address = Address_37 [] address_ = Address_37 instance C_Address Ent38 Ent30 where _address = Address_38 [] address_ = Address_38 instance C_Address Ent40 Ent30 where _address = Address_40 [] address_ = Address_40 instance C_Address Ent41 Ent4 where _address = Address_41 [] address_ = Address_41 instance C_Address Ent42 Ent4 where _address = Address_42 [] address_ = Address_42 instance C_Address Ent43 Ent20 where _address = Address_43 [] address_ = Address_43 instance C_Address Ent44 Ent30 where _address = Address_44 [] address_ = Address_44 instance C_Address Ent45 Ent31 where _address = Address_45 [] address_ = Address_45 instance C_Address Ent46 Ent30 where _address = Address_46 [] address_ = Address_46 instance C_Address Ent47 Ent30 where _address = Address_47 [] address_ = Address_47 class C_Hr a where _hr :: a hr_ :: [Att11] -> a instance C_Hr Ent3 where _hr = Hr_3 [] hr_ = Hr_3 instance C_Hr Ent5 where _hr = Hr_5 [] hr_ = Hr_5 instance C_Hr Ent6 where _hr = Hr_6 [] hr_ = Hr_6 instance C_Hr Ent10 where _hr = Hr_10 [] hr_ = Hr_10 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 Ent19 where _hr = Hr_19 [] hr_ = Hr_19 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 Ent24 where _hr = Hr_24 [] hr_ = Hr_24 instance C_Hr Ent25 where _hr = Hr_25 [] hr_ = Hr_25 instance C_Hr Ent26 where _hr = Hr_26 [] hr_ = Hr_26 instance C_Hr Ent29 where _hr = Hr_29 [] hr_ = Hr_29 instance C_Hr Ent32 where _hr = Hr_32 [] hr_ = Hr_32 instance C_Hr Ent34 where _hr = Hr_34 [] hr_ = Hr_34 instance C_Hr Ent35 where _hr = Hr_35 [] hr_ = Hr_35 instance C_Hr Ent36 where _hr = Hr_36 [] hr_ = Hr_36 instance C_Hr Ent37 where _hr = Hr_37 [] hr_ = Hr_37 instance C_Hr Ent38 where _hr = Hr_38 [] hr_ = Hr_38 instance C_Hr Ent40 where _hr = Hr_40 [] hr_ = Hr_40 instance C_Hr Ent41 where _hr = Hr_41 [] hr_ = Hr_41 instance C_Hr Ent42 where _hr = Hr_42 [] hr_ = Hr_42 instance C_Hr Ent43 where _hr = Hr_43 [] hr_ = Hr_43 instance C_Hr Ent44 where _hr = Hr_44 [] hr_ = Hr_44 instance C_Hr Ent45 where _hr = Hr_45 [] hr_ = Hr_45 instance C_Hr Ent46 where _hr = Hr_46 [] hr_ = Hr_46 instance C_Hr Ent47 where _hr = Hr_47 [] hr_ = Hr_47 class C_Pre a b | a -> b where _pre :: [b] -> a pre_ :: [Att13] -> [b] -> a instance C_Pre Ent3 Ent39 where _pre = Pre_3 [] pre_ = Pre_3 instance C_Pre Ent5 Ent9 where _pre = Pre_5 [] pre_ = Pre_5 instance C_Pre Ent6 Ent9 where _pre = Pre_6 [] pre_ = Pre_6 instance C_Pre Ent10 Ent9 where _pre = Pre_10 [] pre_ = Pre_10 instance C_Pre Ent11 Ent9 where _pre = Pre_11 [] pre_ = Pre_11 instance C_Pre Ent12 Ent9 where _pre = Pre_12 [] pre_ = Pre_12 instance C_Pre Ent17 Ent9 where _pre = Pre_17 [] pre_ = Pre_17 instance C_Pre Ent18 Ent9 where _pre = Pre_18 [] pre_ = Pre_18 instance C_Pre Ent19 Ent9 where _pre = Pre_19 [] pre_ = Pre_19 instance C_Pre Ent21 Ent22 where _pre = Pre_21 [] pre_ = Pre_21 instance C_Pre Ent23 Ent22 where _pre = Pre_23 [] pre_ = Pre_23 instance C_Pre Ent24 Ent22 where _pre = Pre_24 [] pre_ = Pre_24 instance C_Pre Ent25 Ent22 where _pre = Pre_25 [] pre_ = Pre_25 instance C_Pre Ent26 Ent22 where _pre = Pre_26 [] pre_ = Pre_26 instance C_Pre Ent29 Ent22 where _pre = Pre_29 [] pre_ = Pre_29 instance C_Pre Ent32 Ent33 where _pre = Pre_32 [] pre_ = Pre_32 instance C_Pre Ent34 Ent33 where _pre = Pre_34 [] pre_ = Pre_34 instance C_Pre Ent35 Ent33 where _pre = Pre_35 [] pre_ = Pre_35 instance C_Pre Ent36 Ent33 where _pre = Pre_36 [] pre_ = Pre_36 instance C_Pre Ent37 Ent33 where _pre = Pre_37 [] pre_ = Pre_37 instance C_Pre Ent38 Ent39 where _pre = Pre_38 [] pre_ = Pre_38 instance C_Pre Ent40 Ent39 where _pre = Pre_40 [] pre_ = Pre_40 instance C_Pre Ent41 Ent9 where _pre = Pre_41 [] pre_ = Pre_41 instance C_Pre Ent42 Ent9 where _pre = Pre_42 [] pre_ = Pre_42 instance C_Pre Ent43 Ent22 where _pre = Pre_43 [] pre_ = Pre_43 instance C_Pre Ent44 Ent39 where _pre = Pre_44 [] pre_ = Pre_44 instance C_Pre Ent45 Ent33 where _pre = Pre_45 [] pre_ = Pre_45 instance C_Pre Ent46 Ent39 where _pre = Pre_46 [] pre_ = Pre_46 instance C_Pre Ent47 Ent39 where _pre = Pre_47 [] pre_ = Pre_47 class C_Blockquote a b | a -> b where _blockquote :: [b] -> a blockquote_ :: [Att14] -> [b] -> a instance C_Blockquote Ent3 Ent6 where _blockquote = Blockquote_3 [] blockquote_ = Blockquote_3 instance C_Blockquote Ent5 Ent6 where _blockquote = Blockquote_5 [] blockquote_ = Blockquote_5 instance C_Blockquote Ent6 Ent6 where _blockquote = Blockquote_6 [] blockquote_ = Blockquote_6 instance C_Blockquote Ent10 Ent10 where _blockquote = Blockquote_10 [] blockquote_ = Blockquote_10 instance C_Blockquote Ent11 Ent10 where _blockquote = Blockquote_11 [] blockquote_ = Blockquote_11 instance C_Blockquote Ent12 Ent10 where _blockquote = Blockquote_12 [] blockquote_ = Blockquote_12 instance C_Blockquote Ent17 Ent6 where _blockquote = Blockquote_17 [] blockquote_ = Blockquote_17 instance C_Blockquote Ent18 Ent6 where _blockquote = Blockquote_18 [] blockquote_ = Blockquote_18 instance C_Blockquote Ent19 Ent6 where _blockquote = Blockquote_19 [] blockquote_ = Blockquote_19 instance C_Blockquote Ent21 Ent6 where _blockquote = Blockquote_21 [] blockquote_ = Blockquote_21 instance C_Blockquote Ent23 Ent10 where _blockquote = Blockquote_23 [] blockquote_ = Blockquote_23 instance C_Blockquote Ent24 Ent10 where _blockquote = Blockquote_24 [] blockquote_ = Blockquote_24 instance C_Blockquote Ent25 Ent6 where _blockquote = Blockquote_25 [] blockquote_ = Blockquote_25 instance C_Blockquote Ent26 Ent6 where _blockquote = Blockquote_26 [] blockquote_ = Blockquote_26 instance C_Blockquote Ent29 Ent6 where _blockquote = Blockquote_29 [] blockquote_ = Blockquote_29 instance C_Blockquote Ent32 Ent6 where _blockquote = Blockquote_32 [] blockquote_ = Blockquote_32 instance C_Blockquote Ent34 Ent10 where _blockquote = Blockquote_34 [] blockquote_ = Blockquote_34 instance C_Blockquote Ent35 Ent10 where _blockquote = Blockquote_35 [] blockquote_ = Blockquote_35 instance C_Blockquote Ent36 Ent6 where _blockquote = Blockquote_36 [] blockquote_ = Blockquote_36 instance C_Blockquote Ent37 Ent6 where _blockquote = Blockquote_37 [] blockquote_ = Blockquote_37 instance C_Blockquote Ent38 Ent6 where _blockquote = Blockquote_38 [] blockquote_ = Blockquote_38 instance C_Blockquote Ent40 Ent10 where _blockquote = Blockquote_40 [] blockquote_ = Blockquote_40 instance C_Blockquote Ent41 Ent10 where _blockquote = Blockquote_41 [] blockquote_ = Blockquote_41 instance C_Blockquote Ent42 Ent10 where _blockquote = Blockquote_42 [] blockquote_ = Blockquote_42 instance C_Blockquote Ent43 Ent10 where _blockquote = Blockquote_43 [] blockquote_ = Blockquote_43 instance C_Blockquote Ent44 Ent10 where _blockquote = Blockquote_44 [] blockquote_ = Blockquote_44 instance C_Blockquote Ent45 Ent10 where _blockquote = Blockquote_45 [] blockquote_ = Blockquote_45 instance C_Blockquote Ent46 Ent10 where _blockquote = Blockquote_46 [] blockquote_ = Blockquote_46 instance C_Blockquote Ent47 Ent6 where _blockquote = Blockquote_47 [] blockquote_ = Blockquote_47 class C_Ins a b | a -> b where _ins :: [b] -> a ins_ :: [Att15] -> [b] -> a instance C_Ins Ent3 Ent38 where _ins = Ins_3 [] ins_ = Ins_3 instance C_Ins Ent4 Ent5 where _ins = Ins_4 [] ins_ = Ins_4 instance C_Ins Ent5 Ent5 where _ins = Ins_5 [] ins_ = Ins_5 instance C_Ins Ent6 Ent5 where _ins = Ins_6 [] ins_ = Ins_6 instance C_Ins Ent9 Ent5 where _ins = Ins_9 [] ins_ = Ins_9 instance C_Ins Ent10 Ent11 where _ins = Ins_10 [] ins_ = Ins_10 instance C_Ins Ent11 Ent11 where _ins = Ins_11 [] ins_ = Ins_11 instance C_Ins Ent12 Ent11 where _ins = Ins_12 [] ins_ = Ins_12 instance C_Ins Ent17 Ent5 where _ins = Ins_17 [] ins_ = Ins_17 instance C_Ins Ent18 Ent5 where _ins = Ins_18 [] ins_ = Ins_18 instance C_Ins Ent19 Ent5 where _ins = Ins_19 [] ins_ = Ins_19 instance C_Ins Ent20 Ent21 where _ins = Ins_20 [] ins_ = Ins_20 instance C_Ins Ent21 Ent21 where _ins = Ins_21 [] ins_ = Ins_21 instance C_Ins Ent22 Ent21 where _ins = Ins_22 [] ins_ = Ins_22 instance C_Ins Ent23 Ent23 where _ins = Ins_23 [] ins_ = Ins_23 instance C_Ins Ent24 Ent23 where _ins = Ins_24 [] ins_ = Ins_24 instance C_Ins Ent25 Ent21 where _ins = Ins_25 [] ins_ = Ins_25 instance C_Ins Ent26 Ent21 where _ins = Ins_26 [] ins_ = Ins_26 instance C_Ins Ent29 Ent21 where _ins = Ins_29 [] ins_ = Ins_29 instance C_Ins Ent30 Ent38 where _ins = Ins_30 [] ins_ = Ins_30 instance C_Ins Ent31 Ent32 where _ins = Ins_31 [] ins_ = Ins_31 instance C_Ins Ent32 Ent32 where _ins = Ins_32 [] ins_ = Ins_32 instance C_Ins Ent33 Ent32 where _ins = Ins_33 [] ins_ = Ins_33 instance C_Ins Ent34 Ent34 where _ins = Ins_34 [] ins_ = Ins_34 instance C_Ins Ent35 Ent34 where _ins = Ins_35 [] ins_ = Ins_35 instance C_Ins Ent36 Ent32 where _ins = Ins_36 [] ins_ = Ins_36 instance C_Ins Ent37 Ent32 where _ins = Ins_37 [] ins_ = Ins_37 instance C_Ins Ent38 Ent38 where _ins = Ins_38 [] ins_ = Ins_38 instance C_Ins Ent39 Ent38 where _ins = Ins_39 [] ins_ = Ins_39 instance C_Ins Ent40 Ent40 where _ins = Ins_40 [] ins_ = Ins_40 instance C_Ins Ent41 Ent11 where _ins = Ins_41 [] ins_ = Ins_41 instance C_Ins Ent42 Ent11 where _ins = Ins_42 [] ins_ = Ins_42 instance C_Ins Ent43 Ent23 where _ins = Ins_43 [] ins_ = Ins_43 instance C_Ins Ent44 Ent40 where _ins = Ins_44 [] ins_ = Ins_44 instance C_Ins Ent45 Ent34 where _ins = Ins_45 [] ins_ = Ins_45 instance C_Ins Ent46 Ent40 where _ins = Ins_46 [] ins_ = Ins_46 instance C_Ins Ent47 Ent38 where _ins = Ins_47 [] ins_ = Ins_47 class C_Del a b | a -> b where _del :: [b] -> a del_ :: [Att15] -> [b] -> a instance C_Del Ent3 Ent38 where _del = Del_3 [] del_ = Del_3 instance C_Del Ent4 Ent5 where _del = Del_4 [] del_ = Del_4 instance C_Del Ent5 Ent5 where _del = Del_5 [] del_ = Del_5 instance C_Del Ent6 Ent5 where _del = Del_6 [] del_ = Del_6 instance C_Del Ent9 Ent5 where _del = Del_9 [] del_ = Del_9 instance C_Del Ent10 Ent11 where _del = Del_10 [] del_ = Del_10 instance C_Del Ent11 Ent11 where _del = Del_11 [] del_ = Del_11 instance C_Del Ent12 Ent11 where _del = Del_12 [] del_ = Del_12 instance C_Del Ent17 Ent5 where _del = Del_17 [] del_ = Del_17 instance C_Del Ent18 Ent5 where _del = Del_18 [] del_ = Del_18 instance C_Del Ent19 Ent5 where _del = Del_19 [] del_ = Del_19 instance C_Del Ent20 Ent21 where _del = Del_20 [] del_ = Del_20 instance C_Del Ent21 Ent21 where _del = Del_21 [] del_ = Del_21 instance C_Del Ent22 Ent21 where _del = Del_22 [] del_ = Del_22 instance C_Del Ent23 Ent23 where _del = Del_23 [] del_ = Del_23 instance C_Del Ent24 Ent23 where _del = Del_24 [] del_ = Del_24 instance C_Del Ent25 Ent21 where _del = Del_25 [] del_ = Del_25 instance C_Del Ent26 Ent21 where _del = Del_26 [] del_ = Del_26 instance C_Del Ent29 Ent21 where _del = Del_29 [] del_ = Del_29 instance C_Del Ent30 Ent38 where _del = Del_30 [] del_ = Del_30 instance C_Del Ent31 Ent32 where _del = Del_31 [] del_ = Del_31 instance C_Del Ent32 Ent32 where _del = Del_32 [] del_ = Del_32 instance C_Del Ent33 Ent32 where _del = Del_33 [] del_ = Del_33 instance C_Del Ent34 Ent34 where _del = Del_34 [] del_ = Del_34 instance C_Del Ent35 Ent34 where _del = Del_35 [] del_ = Del_35 instance C_Del Ent36 Ent32 where _del = Del_36 [] del_ = Del_36 instance C_Del Ent37 Ent32 where _del = Del_37 [] del_ = Del_37 instance C_Del Ent38 Ent38 where _del = Del_38 [] del_ = Del_38 instance C_Del Ent39 Ent38 where _del = Del_39 [] del_ = Del_39 instance C_Del Ent40 Ent40 where _del = Del_40 [] del_ = Del_40 instance C_Del Ent41 Ent11 where _del = Del_41 [] del_ = Del_41 instance C_Del Ent42 Ent11 where _del = Del_42 [] del_ = Del_42 instance C_Del Ent43 Ent23 where _del = Del_43 [] del_ = Del_43 instance C_Del Ent44 Ent40 where _del = Del_44 [] del_ = Del_44 instance C_Del Ent45 Ent34 where _del = Del_45 [] del_ = Del_45 instance C_Del Ent46 Ent40 where _del = Del_46 [] del_ = Del_46 instance C_Del Ent47 Ent38 where _del = Del_47 [] del_ = Del_47 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 Ent30 Ent4 where _a = A_30 [] a_ = A_30 instance C_A Ent31 Ent20 where _a = A_31 [] a_ = A_31 instance C_A Ent32 Ent20 where _a = A_32 [] a_ = A_32 instance C_A Ent33 Ent20 where _a = A_33 [] a_ = A_33 instance C_A Ent34 Ent20 where _a = A_34 [] a_ = A_34 instance C_A Ent35 Ent20 where _a = A_35 [] a_ = A_35 instance C_A Ent36 Ent20 where _a = A_36 [] a_ = A_36 instance C_A Ent37 Ent20 where _a = A_37 [] a_ = A_37 instance C_A Ent38 Ent4 where _a = A_38 [] a_ = A_38 instance C_A Ent39 Ent4 where _a = A_39 [] a_ = A_39 instance C_A Ent40 Ent4 where _a = A_40 [] a_ = A_40 instance C_A Ent44 Ent4 where _a = A_44 [] a_ = A_44 instance C_A Ent45 Ent20 where _a = A_45 [] a_ = A_45 instance C_A Ent46 Ent4 where _a = A_46 [] a_ = A_46 instance C_A Ent47 Ent4 where _a = A_47 [] a_ = A_47 class C_Span a b | a -> b where _span :: [b] -> a span_ :: [Att11] -> [b] -> a instance C_Span Ent3 Ent30 where _span = Span_3 [] span_ = Span_3 instance C_Span Ent4 Ent4 where _span = Span_4 [] span_ = Span_4 instance C_Span Ent5 Ent4 where _span = Span_5 [] span_ = Span_5 instance C_Span Ent9 Ent4 where _span = Span_9 [] span_ = Span_9 instance C_Span Ent11 Ent4 where _span = Span_11 [] span_ = Span_11 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 Ent18 Ent4 where _span = Span_18 [] span_ = Span_18 instance C_Span Ent20 Ent20 where _span = Span_20 [] span_ = Span_20 instance C_Span Ent21 Ent20 where _span = Span_21 [] span_ = Span_21 instance C_Span Ent22 Ent20 where _span = Span_22 [] span_ = Span_22 instance C_Span Ent23 Ent20 where _span = Span_23 [] span_ = Span_23 instance C_Span Ent24 Ent20 where _span = Span_24 [] span_ = Span_24 instance C_Span Ent25 Ent20 where _span = Span_25 [] span_ = Span_25 instance C_Span Ent26 Ent20 where _span = Span_26 [] span_ = Span_26 instance C_Span Ent29 Ent20 where _span = Span_29 [] span_ = Span_29 instance C_Span Ent30 Ent30 where _span = Span_30 [] span_ = Span_30 instance C_Span Ent31 Ent31 where _span = Span_31 [] span_ = Span_31 instance C_Span Ent32 Ent31 where _span = Span_32 [] span_ = Span_32 instance C_Span Ent33 Ent31 where _span = Span_33 [] span_ = Span_33 instance C_Span Ent34 Ent31 where _span = Span_34 [] span_ = Span_34 instance C_Span Ent35 Ent31 where _span = Span_35 [] span_ = Span_35 instance C_Span Ent36 Ent31 where _span = Span_36 [] span_ = Span_36 instance C_Span Ent37 Ent31 where _span = Span_37 [] span_ = Span_37 instance C_Span Ent38 Ent30 where _span = Span_38 [] span_ = Span_38 instance C_Span Ent39 Ent30 where _span = Span_39 [] span_ = Span_39 instance C_Span Ent40 Ent30 where _span = Span_40 [] span_ = Span_40 instance C_Span Ent41 Ent4 where _span = Span_41 [] span_ = Span_41 instance C_Span Ent43 Ent20 where _span = Span_43 [] span_ = Span_43 instance C_Span Ent44 Ent30 where _span = Span_44 [] span_ = Span_44 instance C_Span Ent45 Ent31 where _span = Span_45 [] span_ = Span_45 instance C_Span Ent46 Ent30 where _span = Span_46 [] span_ = Span_46 instance C_Span Ent47 Ent30 where _span = Span_47 [] span_ = Span_47 class C_Bdo a b | a -> b where _bdo :: [b] -> a bdo_ :: [Att11] -> [b] -> a instance C_Bdo Ent3 Ent30 where _bdo = Bdo_3 [] bdo_ = Bdo_3 instance C_Bdo Ent4 Ent4 where _bdo = Bdo_4 [] bdo_ = Bdo_4 instance C_Bdo Ent5 Ent4 where _bdo = Bdo_5 [] bdo_ = Bdo_5 instance C_Bdo Ent9 Ent4 where _bdo = Bdo_9 [] bdo_ = Bdo_9 instance C_Bdo Ent11 Ent4 where _bdo = Bdo_11 [] bdo_ = Bdo_11 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 Ent18 Ent4 where _bdo = Bdo_18 [] bdo_ = Bdo_18 instance C_Bdo Ent20 Ent20 where _bdo = Bdo_20 [] bdo_ = Bdo_20 instance C_Bdo Ent21 Ent20 where _bdo = Bdo_21 [] bdo_ = Bdo_21 instance C_Bdo Ent22 Ent20 where _bdo = Bdo_22 [] bdo_ = Bdo_22 instance C_Bdo Ent23 Ent20 where _bdo = Bdo_23 [] bdo_ = Bdo_23 instance C_Bdo Ent24 Ent20 where _bdo = Bdo_24 [] bdo_ = Bdo_24 instance C_Bdo Ent25 Ent20 where _bdo = Bdo_25 [] bdo_ = Bdo_25 instance C_Bdo Ent26 Ent20 where _bdo = Bdo_26 [] bdo_ = Bdo_26 instance C_Bdo Ent29 Ent20 where _bdo = Bdo_29 [] bdo_ = Bdo_29 instance C_Bdo Ent30 Ent30 where _bdo = Bdo_30 [] bdo_ = Bdo_30 instance C_Bdo Ent31 Ent31 where _bdo = Bdo_31 [] bdo_ = Bdo_31 instance C_Bdo Ent32 Ent31 where _bdo = Bdo_32 [] bdo_ = Bdo_32 instance C_Bdo Ent33 Ent31 where _bdo = Bdo_33 [] bdo_ = Bdo_33 instance C_Bdo Ent34 Ent31 where _bdo = Bdo_34 [] bdo_ = Bdo_34 instance C_Bdo Ent35 Ent31 where _bdo = Bdo_35 [] bdo_ = Bdo_35 instance C_Bdo Ent36 Ent31 where _bdo = Bdo_36 [] bdo_ = Bdo_36 instance C_Bdo Ent37 Ent31 where _bdo = Bdo_37 [] bdo_ = Bdo_37 instance C_Bdo Ent38 Ent30 where _bdo = Bdo_38 [] bdo_ = Bdo_38 instance C_Bdo Ent39 Ent30 where _bdo = Bdo_39 [] bdo_ = Bdo_39 instance C_Bdo Ent40 Ent30 where _bdo = Bdo_40 [] bdo_ = Bdo_40 instance C_Bdo Ent41 Ent4 where _bdo = Bdo_41 [] bdo_ = Bdo_41 instance C_Bdo Ent43 Ent20 where _bdo = Bdo_43 [] bdo_ = Bdo_43 instance C_Bdo Ent44 Ent30 where _bdo = Bdo_44 [] bdo_ = Bdo_44 instance C_Bdo Ent45 Ent31 where _bdo = Bdo_45 [] bdo_ = Bdo_45 instance C_Bdo Ent46 Ent30 where _bdo = Bdo_46 [] bdo_ = Bdo_46 instance C_Bdo Ent47 Ent30 where _bdo = Bdo_47 [] bdo_ = Bdo_47 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 Ent5 where _br = Br_5 [] br_ = Br_5 instance C_Br Ent9 where _br = Br_9 [] br_ = Br_9 instance C_Br Ent11 where _br = Br_11 [] br_ = Br_11 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 Ent18 where _br = Br_18 [] br_ = Br_18 instance C_Br Ent20 where _br = Br_20 [] br_ = Br_20 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 Ent23 where _br = Br_23 [] br_ = Br_23 instance C_Br Ent24 where _br = Br_24 [] br_ = Br_24 instance C_Br Ent25 where _br = Br_25 [] br_ = Br_25 instance C_Br Ent26 where _br = Br_26 [] br_ = Br_26 instance C_Br Ent29 where _br = Br_29 [] br_ = Br_29 instance C_Br Ent30 where _br = Br_30 [] br_ = Br_30 instance C_Br Ent31 where _br = Br_31 [] br_ = Br_31 instance C_Br Ent32 where _br = Br_32 [] br_ = Br_32 instance C_Br Ent33 where _br = Br_33 [] br_ = Br_33 instance C_Br Ent34 where _br = Br_34 [] br_ = Br_34 instance C_Br Ent35 where _br = Br_35 [] br_ = Br_35 instance C_Br Ent36 where _br = Br_36 [] br_ = Br_36 instance C_Br Ent37 where _br = Br_37 [] br_ = Br_37 instance C_Br Ent38 where _br = Br_38 [] br_ = Br_38 instance C_Br Ent39 where _br = Br_39 [] br_ = Br_39 instance C_Br Ent40 where _br = Br_40 [] br_ = Br_40 instance C_Br Ent41 where _br = Br_41 [] br_ = Br_41 instance C_Br Ent43 where _br = Br_43 [] br_ = Br_43 instance C_Br Ent44 where _br = Br_44 [] br_ = Br_44 instance C_Br Ent45 where _br = Br_45 [] br_ = Br_45 instance C_Br Ent46 where _br = Br_46 [] br_ = Br_46 instance C_Br Ent47 where _br = Br_47 [] br_ = Br_47 class C_Em a b | a -> b where _em :: [b] -> a em_ :: [Att11] -> [b] -> a instance C_Em Ent3 Ent30 where _em = Em_3 [] em_ = Em_3 instance C_Em Ent4 Ent4 where _em = Em_4 [] em_ = Em_4 instance C_Em Ent5 Ent4 where _em = Em_5 [] em_ = Em_5 instance C_Em Ent9 Ent4 where _em = Em_9 [] em_ = Em_9 instance C_Em Ent11 Ent4 where _em = Em_11 [] em_ = Em_11 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 Ent18 Ent4 where _em = Em_18 [] em_ = Em_18 instance C_Em Ent20 Ent20 where _em = Em_20 [] em_ = Em_20 instance C_Em Ent21 Ent20 where _em = Em_21 [] em_ = Em_21 instance C_Em Ent22 Ent20 where _em = Em_22 [] em_ = Em_22 instance C_Em Ent23 Ent20 where _em = Em_23 [] em_ = Em_23 instance C_Em Ent24 Ent20 where _em = Em_24 [] em_ = Em_24 instance C_Em Ent25 Ent20 where _em = Em_25 [] em_ = Em_25 instance C_Em Ent26 Ent20 where _em = Em_26 [] em_ = Em_26 instance C_Em Ent29 Ent20 where _em = Em_29 [] em_ = Em_29 instance C_Em Ent30 Ent30 where _em = Em_30 [] em_ = Em_30 instance C_Em Ent31 Ent31 where _em = Em_31 [] em_ = Em_31 instance C_Em Ent32 Ent31 where _em = Em_32 [] em_ = Em_32 instance C_Em Ent33 Ent31 where _em = Em_33 [] em_ = Em_33 instance C_Em Ent34 Ent31 where _em = Em_34 [] em_ = Em_34 instance C_Em Ent35 Ent31 where _em = Em_35 [] em_ = Em_35 instance C_Em Ent36 Ent31 where _em = Em_36 [] em_ = Em_36 instance C_Em Ent37 Ent31 where _em = Em_37 [] em_ = Em_37 instance C_Em Ent38 Ent30 where _em = Em_38 [] em_ = Em_38 instance C_Em Ent39 Ent30 where _em = Em_39 [] em_ = Em_39 instance C_Em Ent40 Ent30 where _em = Em_40 [] em_ = Em_40 instance C_Em Ent41 Ent4 where _em = Em_41 [] em_ = Em_41 instance C_Em Ent43 Ent20 where _em = Em_43 [] em_ = Em_43 instance C_Em Ent44 Ent30 where _em = Em_44 [] em_ = Em_44 instance C_Em Ent45 Ent31 where _em = Em_45 [] em_ = Em_45 instance C_Em Ent46 Ent30 where _em = Em_46 [] em_ = Em_46 instance C_Em Ent47 Ent30 where _em = Em_47 [] em_ = Em_47 class C_Strong a b | a -> b where _strong :: [b] -> a strong_ :: [Att11] -> [b] -> a instance C_Strong Ent3 Ent30 where _strong = Strong_3 [] strong_ = Strong_3 instance C_Strong Ent4 Ent4 where _strong = Strong_4 [] strong_ = Strong_4 instance C_Strong Ent5 Ent4 where _strong = Strong_5 [] strong_ = Strong_5 instance C_Strong Ent9 Ent4 where _strong = Strong_9 [] strong_ = Strong_9 instance C_Strong Ent11 Ent4 where _strong = Strong_11 [] strong_ = Strong_11 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 Ent18 Ent4 where _strong = Strong_18 [] strong_ = Strong_18 instance C_Strong Ent20 Ent20 where _strong = Strong_20 [] strong_ = Strong_20 instance C_Strong Ent21 Ent20 where _strong = Strong_21 [] strong_ = Strong_21 instance C_Strong Ent22 Ent20 where _strong = Strong_22 [] strong_ = Strong_22 instance C_Strong Ent23 Ent20 where _strong = Strong_23 [] strong_ = Strong_23 instance C_Strong Ent24 Ent20 where _strong = Strong_24 [] strong_ = Strong_24 instance C_Strong Ent25 Ent20 where _strong = Strong_25 [] strong_ = Strong_25 instance C_Strong Ent26 Ent20 where _strong = Strong_26 [] strong_ = Strong_26 instance C_Strong Ent29 Ent20 where _strong = Strong_29 [] strong_ = Strong_29 instance C_Strong Ent30 Ent30 where _strong = Strong_30 [] strong_ = Strong_30 instance C_Strong Ent31 Ent31 where _strong = Strong_31 [] strong_ = Strong_31 instance C_Strong Ent32 Ent31 where _strong = Strong_32 [] strong_ = Strong_32 instance C_Strong Ent33 Ent31 where _strong = Strong_33 [] strong_ = Strong_33 instance C_Strong Ent34 Ent31 where _strong = Strong_34 [] strong_ = Strong_34 instance C_Strong Ent35 Ent31 where _strong = Strong_35 [] strong_ = Strong_35 instance C_Strong Ent36 Ent31 where _strong = Strong_36 [] strong_ = Strong_36 instance C_Strong Ent37 Ent31 where _strong = Strong_37 [] strong_ = Strong_37 instance C_Strong Ent38 Ent30 where _strong = Strong_38 [] strong_ = Strong_38 instance C_Strong Ent39 Ent30 where _strong = Strong_39 [] strong_ = Strong_39 instance C_Strong Ent40 Ent30 where _strong = Strong_40 [] strong_ = Strong_40 instance C_Strong Ent41 Ent4 where _strong = Strong_41 [] strong_ = Strong_41 instance C_Strong Ent43 Ent20 where _strong = Strong_43 [] strong_ = Strong_43 instance C_Strong Ent44 Ent30 where _strong = Strong_44 [] strong_ = Strong_44 instance C_Strong Ent45 Ent31 where _strong = Strong_45 [] strong_ = Strong_45 instance C_Strong Ent46 Ent30 where _strong = Strong_46 [] strong_ = Strong_46 instance C_Strong Ent47 Ent30 where _strong = Strong_47 [] strong_ = Strong_47 class C_Dfn a b | a -> b where _dfn :: [b] -> a dfn_ :: [Att11] -> [b] -> a instance C_Dfn Ent3 Ent30 where _dfn = Dfn_3 [] dfn_ = Dfn_3 instance C_Dfn Ent4 Ent4 where _dfn = Dfn_4 [] dfn_ = Dfn_4 instance C_Dfn Ent5 Ent4 where _dfn = Dfn_5 [] dfn_ = Dfn_5 instance C_Dfn Ent9 Ent4 where _dfn = Dfn_9 [] dfn_ = Dfn_9 instance C_Dfn Ent11 Ent4 where _dfn = Dfn_11 [] dfn_ = Dfn_11 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 Ent18 Ent4 where _dfn = Dfn_18 [] dfn_ = Dfn_18 instance C_Dfn Ent20 Ent20 where _dfn = Dfn_20 [] dfn_ = Dfn_20 instance C_Dfn Ent21 Ent20 where _dfn = Dfn_21 [] dfn_ = Dfn_21 instance C_Dfn Ent22 Ent20 where _dfn = Dfn_22 [] dfn_ = Dfn_22 instance C_Dfn Ent23 Ent20 where _dfn = Dfn_23 [] dfn_ = Dfn_23 instance C_Dfn Ent24 Ent20 where _dfn = Dfn_24 [] dfn_ = Dfn_24 instance C_Dfn Ent25 Ent20 where _dfn = Dfn_25 [] dfn_ = Dfn_25 instance C_Dfn Ent26 Ent20 where _dfn = Dfn_26 [] dfn_ = Dfn_26 instance C_Dfn Ent29 Ent20 where _dfn = Dfn_29 [] dfn_ = Dfn_29 instance C_Dfn Ent30 Ent30 where _dfn = Dfn_30 [] dfn_ = Dfn_30 instance C_Dfn Ent31 Ent31 where _dfn = Dfn_31 [] dfn_ = Dfn_31 instance C_Dfn Ent32 Ent31 where _dfn = Dfn_32 [] dfn_ = Dfn_32 instance C_Dfn Ent33 Ent31 where _dfn = Dfn_33 [] dfn_ = Dfn_33 instance C_Dfn Ent34 Ent31 where _dfn = Dfn_34 [] dfn_ = Dfn_34 instance C_Dfn Ent35 Ent31 where _dfn = Dfn_35 [] dfn_ = Dfn_35 instance C_Dfn Ent36 Ent31 where _dfn = Dfn_36 [] dfn_ = Dfn_36 instance C_Dfn Ent37 Ent31 where _dfn = Dfn_37 [] dfn_ = Dfn_37 instance C_Dfn Ent38 Ent30 where _dfn = Dfn_38 [] dfn_ = Dfn_38 instance C_Dfn Ent39 Ent30 where _dfn = Dfn_39 [] dfn_ = Dfn_39 instance C_Dfn Ent40 Ent30 where _dfn = Dfn_40 [] dfn_ = Dfn_40 instance C_Dfn Ent41 Ent4 where _dfn = Dfn_41 [] dfn_ = Dfn_41 instance C_Dfn Ent43 Ent20 where _dfn = Dfn_43 [] dfn_ = Dfn_43 instance C_Dfn Ent44 Ent30 where _dfn = Dfn_44 [] dfn_ = Dfn_44 instance C_Dfn Ent45 Ent31 where _dfn = Dfn_45 [] dfn_ = Dfn_45 instance C_Dfn Ent46 Ent30 where _dfn = Dfn_46 [] dfn_ = Dfn_46 instance C_Dfn Ent47 Ent30 where _dfn = Dfn_47 [] dfn_ = Dfn_47 class C_Code a b | a -> b where _code :: [b] -> a code_ :: [Att11] -> [b] -> a instance C_Code Ent3 Ent30 where _code = Code_3 [] code_ = Code_3 instance C_Code Ent4 Ent4 where _code = Code_4 [] code_ = Code_4 instance C_Code Ent5 Ent4 where _code = Code_5 [] code_ = Code_5 instance C_Code Ent9 Ent4 where _code = Code_9 [] code_ = Code_9 instance C_Code Ent11 Ent4 where _code = Code_11 [] code_ = Code_11 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 Ent18 Ent4 where _code = Code_18 [] code_ = Code_18 instance C_Code Ent20 Ent20 where _code = Code_20 [] code_ = Code_20 instance C_Code Ent21 Ent20 where _code = Code_21 [] code_ = Code_21 instance C_Code Ent22 Ent20 where _code = Code_22 [] code_ = Code_22 instance C_Code Ent23 Ent20 where _code = Code_23 [] code_ = Code_23 instance C_Code Ent24 Ent20 where _code = Code_24 [] code_ = Code_24 instance C_Code Ent25 Ent20 where _code = Code_25 [] code_ = Code_25 instance C_Code Ent26 Ent20 where _code = Code_26 [] code_ = Code_26 instance C_Code Ent29 Ent20 where _code = Code_29 [] code_ = Code_29 instance C_Code Ent30 Ent30 where _code = Code_30 [] code_ = Code_30 instance C_Code Ent31 Ent31 where _code = Code_31 [] code_ = Code_31 instance C_Code Ent32 Ent31 where _code = Code_32 [] code_ = Code_32 instance C_Code Ent33 Ent31 where _code = Code_33 [] code_ = Code_33 instance C_Code Ent34 Ent31 where _code = Code_34 [] code_ = Code_34 instance C_Code Ent35 Ent31 where _code = Code_35 [] code_ = Code_35 instance C_Code Ent36 Ent31 where _code = Code_36 [] code_ = Code_36 instance C_Code Ent37 Ent31 where _code = Code_37 [] code_ = Code_37 instance C_Code Ent38 Ent30 where _code = Code_38 [] code_ = Code_38 instance C_Code Ent39 Ent30 where _code = Code_39 [] code_ = Code_39 instance C_Code Ent40 Ent30 where _code = Code_40 [] code_ = Code_40 instance C_Code Ent41 Ent4 where _code = Code_41 [] code_ = Code_41 instance C_Code Ent43 Ent20 where _code = Code_43 [] code_ = Code_43 instance C_Code Ent44 Ent30 where _code = Code_44 [] code_ = Code_44 instance C_Code Ent45 Ent31 where _code = Code_45 [] code_ = Code_45 instance C_Code Ent46 Ent30 where _code = Code_46 [] code_ = Code_46 instance C_Code Ent47 Ent30 where _code = Code_47 [] code_ = Code_47 class C_Samp a b | a -> b where _samp :: [b] -> a samp_ :: [Att11] -> [b] -> a instance C_Samp Ent3 Ent30 where _samp = Samp_3 [] samp_ = Samp_3 instance C_Samp Ent4 Ent4 where _samp = Samp_4 [] samp_ = Samp_4 instance C_Samp Ent5 Ent4 where _samp = Samp_5 [] samp_ = Samp_5 instance C_Samp Ent9 Ent4 where _samp = Samp_9 [] samp_ = Samp_9 instance C_Samp Ent11 Ent4 where _samp = Samp_11 [] samp_ = Samp_11 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 Ent18 Ent4 where _samp = Samp_18 [] samp_ = Samp_18 instance C_Samp Ent20 Ent20 where _samp = Samp_20 [] samp_ = Samp_20 instance C_Samp Ent21 Ent20 where _samp = Samp_21 [] samp_ = Samp_21 instance C_Samp Ent22 Ent20 where _samp = Samp_22 [] samp_ = Samp_22 instance C_Samp Ent23 Ent20 where _samp = Samp_23 [] samp_ = Samp_23 instance C_Samp Ent24 Ent20 where _samp = Samp_24 [] samp_ = Samp_24 instance C_Samp Ent25 Ent20 where _samp = Samp_25 [] samp_ = Samp_25 instance C_Samp Ent26 Ent20 where _samp = Samp_26 [] samp_ = Samp_26 instance C_Samp Ent29 Ent20 where _samp = Samp_29 [] samp_ = Samp_29 instance C_Samp Ent30 Ent30 where _samp = Samp_30 [] samp_ = Samp_30 instance C_Samp Ent31 Ent31 where _samp = Samp_31 [] samp_ = Samp_31 instance C_Samp Ent32 Ent31 where _samp = Samp_32 [] samp_ = Samp_32 instance C_Samp Ent33 Ent31 where _samp = Samp_33 [] samp_ = Samp_33 instance C_Samp Ent34 Ent31 where _samp = Samp_34 [] samp_ = Samp_34 instance C_Samp Ent35 Ent31 where _samp = Samp_35 [] samp_ = Samp_35 instance C_Samp Ent36 Ent31 where _samp = Samp_36 [] samp_ = Samp_36 instance C_Samp Ent37 Ent31 where _samp = Samp_37 [] samp_ = Samp_37 instance C_Samp Ent38 Ent30 where _samp = Samp_38 [] samp_ = Samp_38 instance C_Samp Ent39 Ent30 where _samp = Samp_39 [] samp_ = Samp_39 instance C_Samp Ent40 Ent30 where _samp = Samp_40 [] samp_ = Samp_40 instance C_Samp Ent41 Ent4 where _samp = Samp_41 [] samp_ = Samp_41 instance C_Samp Ent43 Ent20 where _samp = Samp_43 [] samp_ = Samp_43 instance C_Samp Ent44 Ent30 where _samp = Samp_44 [] samp_ = Samp_44 instance C_Samp Ent45 Ent31 where _samp = Samp_45 [] samp_ = Samp_45 instance C_Samp Ent46 Ent30 where _samp = Samp_46 [] samp_ = Samp_46 instance C_Samp Ent47 Ent30 where _samp = Samp_47 [] samp_ = Samp_47 class C_Kbd a b | a -> b where _kbd :: [b] -> a kbd_ :: [Att11] -> [b] -> a instance C_Kbd Ent3 Ent30 where _kbd = Kbd_3 [] kbd_ = Kbd_3 instance C_Kbd Ent4 Ent4 where _kbd = Kbd_4 [] kbd_ = Kbd_4 instance C_Kbd Ent5 Ent4 where _kbd = Kbd_5 [] kbd_ = Kbd_5 instance C_Kbd Ent9 Ent4 where _kbd = Kbd_9 [] kbd_ = Kbd_9 instance C_Kbd Ent11 Ent4 where _kbd = Kbd_11 [] kbd_ = Kbd_11 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 Ent18 Ent4 where _kbd = Kbd_18 [] kbd_ = Kbd_18 instance C_Kbd Ent20 Ent20 where _kbd = Kbd_20 [] kbd_ = Kbd_20 instance C_Kbd Ent21 Ent20 where _kbd = Kbd_21 [] kbd_ = Kbd_21 instance C_Kbd Ent22 Ent20 where _kbd = Kbd_22 [] kbd_ = Kbd_22 instance C_Kbd Ent23 Ent20 where _kbd = Kbd_23 [] kbd_ = Kbd_23 instance C_Kbd Ent24 Ent20 where _kbd = Kbd_24 [] kbd_ = Kbd_24 instance C_Kbd Ent25 Ent20 where _kbd = Kbd_25 [] kbd_ = Kbd_25 instance C_Kbd Ent26 Ent20 where _kbd = Kbd_26 [] kbd_ = Kbd_26 instance C_Kbd Ent29 Ent20 where _kbd = Kbd_29 [] kbd_ = Kbd_29 instance C_Kbd Ent30 Ent30 where _kbd = Kbd_30 [] kbd_ = Kbd_30 instance C_Kbd Ent31 Ent31 where _kbd = Kbd_31 [] kbd_ = Kbd_31 instance C_Kbd Ent32 Ent31 where _kbd = Kbd_32 [] kbd_ = Kbd_32 instance C_Kbd Ent33 Ent31 where _kbd = Kbd_33 [] kbd_ = Kbd_33 instance C_Kbd Ent34 Ent31 where _kbd = Kbd_34 [] kbd_ = Kbd_34 instance C_Kbd Ent35 Ent31 where _kbd = Kbd_35 [] kbd_ = Kbd_35 instance C_Kbd Ent36 Ent31 where _kbd = Kbd_36 [] kbd_ = Kbd_36 instance C_Kbd Ent37 Ent31 where _kbd = Kbd_37 [] kbd_ = Kbd_37 instance C_Kbd Ent38 Ent30 where _kbd = Kbd_38 [] kbd_ = Kbd_38 instance C_Kbd Ent39 Ent30 where _kbd = Kbd_39 [] kbd_ = Kbd_39 instance C_Kbd Ent40 Ent30 where _kbd = Kbd_40 [] kbd_ = Kbd_40 instance C_Kbd Ent41 Ent4 where _kbd = Kbd_41 [] kbd_ = Kbd_41 instance C_Kbd Ent43 Ent20 where _kbd = Kbd_43 [] kbd_ = Kbd_43 instance C_Kbd Ent44 Ent30 where _kbd = Kbd_44 [] kbd_ = Kbd_44 instance C_Kbd Ent45 Ent31 where _kbd = Kbd_45 [] kbd_ = Kbd_45 instance C_Kbd Ent46 Ent30 where _kbd = Kbd_46 [] kbd_ = Kbd_46 instance C_Kbd Ent47 Ent30 where _kbd = Kbd_47 [] kbd_ = Kbd_47 class C_Var a b | a -> b where _var :: [b] -> a var_ :: [Att11] -> [b] -> a instance C_Var Ent3 Ent30 where _var = Var_3 [] var_ = Var_3 instance C_Var Ent4 Ent4 where _var = Var_4 [] var_ = Var_4 instance C_Var Ent5 Ent4 where _var = Var_5 [] var_ = Var_5 instance C_Var Ent9 Ent4 where _var = Var_9 [] var_ = Var_9 instance C_Var Ent11 Ent4 where _var = Var_11 [] var_ = Var_11 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 Ent18 Ent4 where _var = Var_18 [] var_ = Var_18 instance C_Var Ent20 Ent20 where _var = Var_20 [] var_ = Var_20 instance C_Var Ent21 Ent20 where _var = Var_21 [] var_ = Var_21 instance C_Var Ent22 Ent20 where _var = Var_22 [] var_ = Var_22 instance C_Var Ent23 Ent20 where _var = Var_23 [] var_ = Var_23 instance C_Var Ent24 Ent20 where _var = Var_24 [] var_ = Var_24 instance C_Var Ent25 Ent20 where _var = Var_25 [] var_ = Var_25 instance C_Var Ent26 Ent20 where _var = Var_26 [] var_ = Var_26 instance C_Var Ent29 Ent20 where _var = Var_29 [] var_ = Var_29 instance C_Var Ent30 Ent30 where _var = Var_30 [] var_ = Var_30 instance C_Var Ent31 Ent31 where _var = Var_31 [] var_ = Var_31 instance C_Var Ent32 Ent31 where _var = Var_32 [] var_ = Var_32 instance C_Var Ent33 Ent31 where _var = Var_33 [] var_ = Var_33 instance C_Var Ent34 Ent31 where _var = Var_34 [] var_ = Var_34 instance C_Var Ent35 Ent31 where _var = Var_35 [] var_ = Var_35 instance C_Var Ent36 Ent31 where _var = Var_36 [] var_ = Var_36 instance C_Var Ent37 Ent31 where _var = Var_37 [] var_ = Var_37 instance C_Var Ent38 Ent30 where _var = Var_38 [] var_ = Var_38 instance C_Var Ent39 Ent30 where _var = Var_39 [] var_ = Var_39 instance C_Var Ent40 Ent30 where _var = Var_40 [] var_ = Var_40 instance C_Var Ent41 Ent4 where _var = Var_41 [] var_ = Var_41 instance C_Var Ent43 Ent20 where _var = Var_43 [] var_ = Var_43 instance C_Var Ent44 Ent30 where _var = Var_44 [] var_ = Var_44 instance C_Var Ent45 Ent31 where _var = Var_45 [] var_ = Var_45 instance C_Var Ent46 Ent30 where _var = Var_46 [] var_ = Var_46 instance C_Var Ent47 Ent30 where _var = Var_47 [] var_ = Var_47 class C_Cite a b | a -> b where _cite :: [b] -> a cite_ :: [Att11] -> [b] -> a instance C_Cite Ent3 Ent30 where _cite = Cite_3 [] cite_ = Cite_3 instance C_Cite Ent4 Ent4 where _cite = Cite_4 [] cite_ = Cite_4 instance C_Cite Ent5 Ent4 where _cite = Cite_5 [] cite_ = Cite_5 instance C_Cite Ent9 Ent4 where _cite = Cite_9 [] cite_ = Cite_9 instance C_Cite Ent11 Ent4 where _cite = Cite_11 [] cite_ = Cite_11 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 Ent18 Ent4 where _cite = Cite_18 [] cite_ = Cite_18 instance C_Cite Ent20 Ent20 where _cite = Cite_20 [] cite_ = Cite_20 instance C_Cite Ent21 Ent20 where _cite = Cite_21 [] cite_ = Cite_21 instance C_Cite Ent22 Ent20 where _cite = Cite_22 [] cite_ = Cite_22 instance C_Cite Ent23 Ent20 where _cite = Cite_23 [] cite_ = Cite_23 instance C_Cite Ent24 Ent20 where _cite = Cite_24 [] cite_ = Cite_24 instance C_Cite Ent25 Ent20 where _cite = Cite_25 [] cite_ = Cite_25 instance C_Cite Ent26 Ent20 where _cite = Cite_26 [] cite_ = Cite_26 instance C_Cite Ent29 Ent20 where _cite = Cite_29 [] cite_ = Cite_29 instance C_Cite Ent30 Ent30 where _cite = Cite_30 [] cite_ = Cite_30 instance C_Cite Ent31 Ent31 where _cite = Cite_31 [] cite_ = Cite_31 instance C_Cite Ent32 Ent31 where _cite = Cite_32 [] cite_ = Cite_32 instance C_Cite Ent33 Ent31 where _cite = Cite_33 [] cite_ = Cite_33 instance C_Cite Ent34 Ent31 where _cite = Cite_34 [] cite_ = Cite_34 instance C_Cite Ent35 Ent31 where _cite = Cite_35 [] cite_ = Cite_35 instance C_Cite Ent36 Ent31 where _cite = Cite_36 [] cite_ = Cite_36 instance C_Cite Ent37 Ent31 where _cite = Cite_37 [] cite_ = Cite_37 instance C_Cite Ent38 Ent30 where _cite = Cite_38 [] cite_ = Cite_38 instance C_Cite Ent39 Ent30 where _cite = Cite_39 [] cite_ = Cite_39 instance C_Cite Ent40 Ent30 where _cite = Cite_40 [] cite_ = Cite_40 instance C_Cite Ent41 Ent4 where _cite = Cite_41 [] cite_ = Cite_41 instance C_Cite Ent43 Ent20 where _cite = Cite_43 [] cite_ = Cite_43 instance C_Cite Ent44 Ent30 where _cite = Cite_44 [] cite_ = Cite_44 instance C_Cite Ent45 Ent31 where _cite = Cite_45 [] cite_ = Cite_45 instance C_Cite Ent46 Ent30 where _cite = Cite_46 [] cite_ = Cite_46 instance C_Cite Ent47 Ent30 where _cite = Cite_47 [] cite_ = Cite_47 class C_Abbr a b | a -> b where _abbr :: [b] -> a abbr_ :: [Att11] -> [b] -> a instance C_Abbr Ent3 Ent30 where _abbr = Abbr_3 [] abbr_ = Abbr_3 instance C_Abbr Ent4 Ent4 where _abbr = Abbr_4 [] abbr_ = Abbr_4 instance C_Abbr Ent5 Ent4 where _abbr = Abbr_5 [] abbr_ = Abbr_5 instance C_Abbr Ent9 Ent4 where _abbr = Abbr_9 [] abbr_ = Abbr_9 instance C_Abbr Ent11 Ent4 where _abbr = Abbr_11 [] abbr_ = Abbr_11 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 Ent18 Ent4 where _abbr = Abbr_18 [] abbr_ = Abbr_18 instance C_Abbr Ent20 Ent20 where _abbr = Abbr_20 [] abbr_ = Abbr_20 instance C_Abbr Ent21 Ent20 where _abbr = Abbr_21 [] abbr_ = Abbr_21 instance C_Abbr Ent22 Ent20 where _abbr = Abbr_22 [] abbr_ = Abbr_22 instance C_Abbr Ent23 Ent20 where _abbr = Abbr_23 [] abbr_ = Abbr_23 instance C_Abbr Ent24 Ent20 where _abbr = Abbr_24 [] abbr_ = Abbr_24 instance C_Abbr Ent25 Ent20 where _abbr = Abbr_25 [] abbr_ = Abbr_25 instance C_Abbr Ent26 Ent20 where _abbr = Abbr_26 [] abbr_ = Abbr_26 instance C_Abbr Ent29 Ent20 where _abbr = Abbr_29 [] abbr_ = Abbr_29 instance C_Abbr Ent30 Ent30 where _abbr = Abbr_30 [] abbr_ = Abbr_30 instance C_Abbr Ent31 Ent31 where _abbr = Abbr_31 [] abbr_ = Abbr_31 instance C_Abbr Ent32 Ent31 where _abbr = Abbr_32 [] abbr_ = Abbr_32 instance C_Abbr Ent33 Ent31 where _abbr = Abbr_33 [] abbr_ = Abbr_33 instance C_Abbr Ent34 Ent31 where _abbr = Abbr_34 [] abbr_ = Abbr_34 instance C_Abbr Ent35 Ent31 where _abbr = Abbr_35 [] abbr_ = Abbr_35 instance C_Abbr Ent36 Ent31 where _abbr = Abbr_36 [] abbr_ = Abbr_36 instance C_Abbr Ent37 Ent31 where _abbr = Abbr_37 [] abbr_ = Abbr_37 instance C_Abbr Ent38 Ent30 where _abbr = Abbr_38 [] abbr_ = Abbr_38 instance C_Abbr Ent39 Ent30 where _abbr = Abbr_39 [] abbr_ = Abbr_39 instance C_Abbr Ent40 Ent30 where _abbr = Abbr_40 [] abbr_ = Abbr_40 instance C_Abbr Ent41 Ent4 where _abbr = Abbr_41 [] abbr_ = Abbr_41 instance C_Abbr Ent43 Ent20 where _abbr = Abbr_43 [] abbr_ = Abbr_43 instance C_Abbr Ent44 Ent30 where _abbr = Abbr_44 [] abbr_ = Abbr_44 instance C_Abbr Ent45 Ent31 where _abbr = Abbr_45 [] abbr_ = Abbr_45 instance C_Abbr Ent46 Ent30 where _abbr = Abbr_46 [] abbr_ = Abbr_46 instance C_Abbr Ent47 Ent30 where _abbr = Abbr_47 [] abbr_ = Abbr_47 class C_Acronym a b | a -> b where _acronym :: [b] -> a acronym_ :: [Att11] -> [b] -> a instance C_Acronym Ent3 Ent30 where _acronym = Acronym_3 [] acronym_ = Acronym_3 instance C_Acronym Ent4 Ent4 where _acronym = Acronym_4 [] acronym_ = Acronym_4 instance C_Acronym Ent5 Ent4 where _acronym = Acronym_5 [] acronym_ = Acronym_5 instance C_Acronym Ent9 Ent4 where _acronym = Acronym_9 [] acronym_ = Acronym_9 instance C_Acronym Ent11 Ent4 where _acronym = Acronym_11 [] acronym_ = Acronym_11 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 Ent18 Ent4 where _acronym = Acronym_18 [] acronym_ = Acronym_18 instance C_Acronym Ent20 Ent20 where _acronym = Acronym_20 [] acronym_ = Acronym_20 instance C_Acronym Ent21 Ent20 where _acronym = Acronym_21 [] acronym_ = Acronym_21 instance C_Acronym Ent22 Ent20 where _acronym = Acronym_22 [] acronym_ = Acronym_22 instance C_Acronym Ent23 Ent20 where _acronym = Acronym_23 [] acronym_ = Acronym_23 instance C_Acronym Ent24 Ent20 where _acronym = Acronym_24 [] acronym_ = Acronym_24 instance C_Acronym Ent25 Ent20 where _acronym = Acronym_25 [] acronym_ = Acronym_25 instance C_Acronym Ent26 Ent20 where _acronym = Acronym_26 [] acronym_ = Acronym_26 instance C_Acronym Ent29 Ent20 where _acronym = Acronym_29 [] acronym_ = Acronym_29 instance C_Acronym Ent30 Ent30 where _acronym = Acronym_30 [] acronym_ = Acronym_30 instance C_Acronym Ent31 Ent31 where _acronym = Acronym_31 [] acronym_ = Acronym_31 instance C_Acronym Ent32 Ent31 where _acronym = Acronym_32 [] acronym_ = Acronym_32 instance C_Acronym Ent33 Ent31 where _acronym = Acronym_33 [] acronym_ = Acronym_33 instance C_Acronym Ent34 Ent31 where _acronym = Acronym_34 [] acronym_ = Acronym_34 instance C_Acronym Ent35 Ent31 where _acronym = Acronym_35 [] acronym_ = Acronym_35 instance C_Acronym Ent36 Ent31 where _acronym = Acronym_36 [] acronym_ = Acronym_36 instance C_Acronym Ent37 Ent31 where _acronym = Acronym_37 [] acronym_ = Acronym_37 instance C_Acronym Ent38 Ent30 where _acronym = Acronym_38 [] acronym_ = Acronym_38 instance C_Acronym Ent39 Ent30 where _acronym = Acronym_39 [] acronym_ = Acronym_39 instance C_Acronym Ent40 Ent30 where _acronym = Acronym_40 [] acronym_ = Acronym_40 instance C_Acronym Ent41 Ent4 where _acronym = Acronym_41 [] acronym_ = Acronym_41 instance C_Acronym Ent43 Ent20 where _acronym = Acronym_43 [] acronym_ = Acronym_43 instance C_Acronym Ent44 Ent30 where _acronym = Acronym_44 [] acronym_ = Acronym_44 instance C_Acronym Ent45 Ent31 where _acronym = Acronym_45 [] acronym_ = Acronym_45 instance C_Acronym Ent46 Ent30 where _acronym = Acronym_46 [] acronym_ = Acronym_46 instance C_Acronym Ent47 Ent30 where _acronym = Acronym_47 [] acronym_ = Acronym_47 class C_Q a b | a -> b where _q :: [b] -> a q_ :: [Att14] -> [b] -> a instance C_Q Ent3 Ent30 where _q = Q_3 [] q_ = Q_3 instance C_Q Ent4 Ent4 where _q = Q_4 [] q_ = Q_4 instance C_Q Ent5 Ent4 where _q = Q_5 [] q_ = Q_5 instance C_Q Ent9 Ent4 where _q = Q_9 [] q_ = Q_9 instance C_Q Ent11 Ent4 where _q = Q_11 [] q_ = Q_11 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 Ent18 Ent4 where _q = Q_18 [] q_ = Q_18 instance C_Q Ent20 Ent20 where _q = Q_20 [] q_ = Q_20 instance C_Q Ent21 Ent20 where _q = Q_21 [] q_ = Q_21 instance C_Q Ent22 Ent20 where _q = Q_22 [] q_ = Q_22 instance C_Q Ent23 Ent20 where _q = Q_23 [] q_ = Q_23 instance C_Q Ent24 Ent20 where _q = Q_24 [] q_ = Q_24 instance C_Q Ent25 Ent20 where _q = Q_25 [] q_ = Q_25 instance C_Q Ent26 Ent20 where _q = Q_26 [] q_ = Q_26 instance C_Q Ent29 Ent20 where _q = Q_29 [] q_ = Q_29 instance C_Q Ent30 Ent30 where _q = Q_30 [] q_ = Q_30 instance C_Q Ent31 Ent31 where _q = Q_31 [] q_ = Q_31 instance C_Q Ent32 Ent31 where _q = Q_32 [] q_ = Q_32 instance C_Q Ent33 Ent31 where _q = Q_33 [] q_ = Q_33 instance C_Q Ent34 Ent31 where _q = Q_34 [] q_ = Q_34 instance C_Q Ent35 Ent31 where _q = Q_35 [] q_ = Q_35 instance C_Q Ent36 Ent31 where _q = Q_36 [] q_ = Q_36 instance C_Q Ent37 Ent31 where _q = Q_37 [] q_ = Q_37 instance C_Q Ent38 Ent30 where _q = Q_38 [] q_ = Q_38 instance C_Q Ent39 Ent30 where _q = Q_39 [] q_ = Q_39 instance C_Q Ent40 Ent30 where _q = Q_40 [] q_ = Q_40 instance C_Q Ent41 Ent4 where _q = Q_41 [] q_ = Q_41 instance C_Q Ent43 Ent20 where _q = Q_43 [] q_ = Q_43 instance C_Q Ent44 Ent30 where _q = Q_44 [] q_ = Q_44 instance C_Q Ent45 Ent31 where _q = Q_45 [] q_ = Q_45 instance C_Q Ent46 Ent30 where _q = Q_46 [] q_ = Q_46 instance C_Q Ent47 Ent30 where _q = Q_47 [] q_ = Q_47 class C_Sub a b | a -> b where _sub :: [b] -> a sub_ :: [Att11] -> [b] -> a instance C_Sub Ent3 Ent30 where _sub = Sub_3 [] sub_ = Sub_3 instance C_Sub Ent4 Ent4 where _sub = Sub_4 [] sub_ = Sub_4 instance C_Sub Ent5 Ent4 where _sub = Sub_5 [] sub_ = Sub_5 instance C_Sub Ent9 Ent4 where _sub = Sub_9 [] sub_ = Sub_9 instance C_Sub Ent11 Ent4 where _sub = Sub_11 [] sub_ = Sub_11 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 Ent18 Ent4 where _sub = Sub_18 [] sub_ = Sub_18 instance C_Sub Ent20 Ent20 where _sub = Sub_20 [] sub_ = Sub_20 instance C_Sub Ent21 Ent20 where _sub = Sub_21 [] sub_ = Sub_21 instance C_Sub Ent22 Ent20 where _sub = Sub_22 [] sub_ = Sub_22 instance C_Sub Ent23 Ent20 where _sub = Sub_23 [] sub_ = Sub_23 instance C_Sub Ent24 Ent20 where _sub = Sub_24 [] sub_ = Sub_24 instance C_Sub Ent25 Ent20 where _sub = Sub_25 [] sub_ = Sub_25 instance C_Sub Ent26 Ent20 where _sub = Sub_26 [] sub_ = Sub_26 instance C_Sub Ent29 Ent20 where _sub = Sub_29 [] sub_ = Sub_29 instance C_Sub Ent30 Ent30 where _sub = Sub_30 [] sub_ = Sub_30 instance C_Sub Ent31 Ent31 where _sub = Sub_31 [] sub_ = Sub_31 instance C_Sub Ent32 Ent31 where _sub = Sub_32 [] sub_ = Sub_32 instance C_Sub Ent33 Ent31 where _sub = Sub_33 [] sub_ = Sub_33 instance C_Sub Ent34 Ent31 where _sub = Sub_34 [] sub_ = Sub_34 instance C_Sub Ent35 Ent31 where _sub = Sub_35 [] sub_ = Sub_35 instance C_Sub Ent36 Ent31 where _sub = Sub_36 [] sub_ = Sub_36 instance C_Sub Ent37 Ent31 where _sub = Sub_37 [] sub_ = Sub_37 instance C_Sub Ent38 Ent30 where _sub = Sub_38 [] sub_ = Sub_38 instance C_Sub Ent39 Ent30 where _sub = Sub_39 [] sub_ = Sub_39 instance C_Sub Ent40 Ent30 where _sub = Sub_40 [] sub_ = Sub_40 instance C_Sub Ent41 Ent4 where _sub = Sub_41 [] sub_ = Sub_41 instance C_Sub Ent43 Ent20 where _sub = Sub_43 [] sub_ = Sub_43 instance C_Sub Ent44 Ent30 where _sub = Sub_44 [] sub_ = Sub_44 instance C_Sub Ent45 Ent31 where _sub = Sub_45 [] sub_ = Sub_45 instance C_Sub Ent46 Ent30 where _sub = Sub_46 [] sub_ = Sub_46 instance C_Sub Ent47 Ent30 where _sub = Sub_47 [] sub_ = Sub_47 class C_Sup a b | a -> b where _sup :: [b] -> a sup_ :: [Att11] -> [b] -> a instance C_Sup Ent3 Ent30 where _sup = Sup_3 [] sup_ = Sup_3 instance C_Sup Ent4 Ent4 where _sup = Sup_4 [] sup_ = Sup_4 instance C_Sup Ent5 Ent4 where _sup = Sup_5 [] sup_ = Sup_5 instance C_Sup Ent9 Ent4 where _sup = Sup_9 [] sup_ = Sup_9 instance C_Sup Ent11 Ent4 where _sup = Sup_11 [] sup_ = Sup_11 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 Ent18 Ent4 where _sup = Sup_18 [] sup_ = Sup_18 instance C_Sup Ent20 Ent20 where _sup = Sup_20 [] sup_ = Sup_20 instance C_Sup Ent21 Ent20 where _sup = Sup_21 [] sup_ = Sup_21 instance C_Sup Ent22 Ent20 where _sup = Sup_22 [] sup_ = Sup_22 instance C_Sup Ent23 Ent20 where _sup = Sup_23 [] sup_ = Sup_23 instance C_Sup Ent24 Ent20 where _sup = Sup_24 [] sup_ = Sup_24 instance C_Sup Ent25 Ent20 where _sup = Sup_25 [] sup_ = Sup_25 instance C_Sup Ent26 Ent20 where _sup = Sup_26 [] sup_ = Sup_26 instance C_Sup Ent29 Ent20 where _sup = Sup_29 [] sup_ = Sup_29 instance C_Sup Ent30 Ent30 where _sup = Sup_30 [] sup_ = Sup_30 instance C_Sup Ent31 Ent31 where _sup = Sup_31 [] sup_ = Sup_31 instance C_Sup Ent32 Ent31 where _sup = Sup_32 [] sup_ = Sup_32 instance C_Sup Ent33 Ent31 where _sup = Sup_33 [] sup_ = Sup_33 instance C_Sup Ent34 Ent31 where _sup = Sup_34 [] sup_ = Sup_34 instance C_Sup Ent35 Ent31 where _sup = Sup_35 [] sup_ = Sup_35 instance C_Sup Ent36 Ent31 where _sup = Sup_36 [] sup_ = Sup_36 instance C_Sup Ent37 Ent31 where _sup = Sup_37 [] sup_ = Sup_37 instance C_Sup Ent38 Ent30 where _sup = Sup_38 [] sup_ = Sup_38 instance C_Sup Ent39 Ent30 where _sup = Sup_39 [] sup_ = Sup_39 instance C_Sup Ent40 Ent30 where _sup = Sup_40 [] sup_ = Sup_40 instance C_Sup Ent41 Ent4 where _sup = Sup_41 [] sup_ = Sup_41 instance C_Sup Ent43 Ent20 where _sup = Sup_43 [] sup_ = Sup_43 instance C_Sup Ent44 Ent30 where _sup = Sup_44 [] sup_ = Sup_44 instance C_Sup Ent45 Ent31 where _sup = Sup_45 [] sup_ = Sup_45 instance C_Sup Ent46 Ent30 where _sup = Sup_46 [] sup_ = Sup_46 instance C_Sup Ent47 Ent30 where _sup = Sup_47 [] sup_ = Sup_47 class C_Tt a b | a -> b where _tt :: [b] -> a tt_ :: [Att11] -> [b] -> a instance C_Tt Ent3 Ent30 where _tt = Tt_3 [] tt_ = Tt_3 instance C_Tt Ent4 Ent4 where _tt = Tt_4 [] tt_ = Tt_4 instance C_Tt Ent5 Ent4 where _tt = Tt_5 [] tt_ = Tt_5 instance C_Tt Ent9 Ent4 where _tt = Tt_9 [] tt_ = Tt_9 instance C_Tt Ent11 Ent4 where _tt = Tt_11 [] tt_ = Tt_11 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 Ent18 Ent4 where _tt = Tt_18 [] tt_ = Tt_18 instance C_Tt Ent20 Ent20 where _tt = Tt_20 [] tt_ = Tt_20 instance C_Tt Ent21 Ent20 where _tt = Tt_21 [] tt_ = Tt_21 instance C_Tt Ent22 Ent20 where _tt = Tt_22 [] tt_ = Tt_22 instance C_Tt Ent23 Ent20 where _tt = Tt_23 [] tt_ = Tt_23 instance C_Tt Ent24 Ent20 where _tt = Tt_24 [] tt_ = Tt_24 instance C_Tt Ent25 Ent20 where _tt = Tt_25 [] tt_ = Tt_25 instance C_Tt Ent26 Ent20 where _tt = Tt_26 [] tt_ = Tt_26 instance C_Tt Ent29 Ent20 where _tt = Tt_29 [] tt_ = Tt_29 instance C_Tt Ent30 Ent30 where _tt = Tt_30 [] tt_ = Tt_30 instance C_Tt Ent31 Ent31 where _tt = Tt_31 [] tt_ = Tt_31 instance C_Tt Ent32 Ent31 where _tt = Tt_32 [] tt_ = Tt_32 instance C_Tt Ent33 Ent31 where _tt = Tt_33 [] tt_ = Tt_33 instance C_Tt Ent34 Ent31 where _tt = Tt_34 [] tt_ = Tt_34 instance C_Tt Ent35 Ent31 where _tt = Tt_35 [] tt_ = Tt_35 instance C_Tt Ent36 Ent31 where _tt = Tt_36 [] tt_ = Tt_36 instance C_Tt Ent37 Ent31 where _tt = Tt_37 [] tt_ = Tt_37 instance C_Tt Ent38 Ent30 where _tt = Tt_38 [] tt_ = Tt_38 instance C_Tt Ent39 Ent30 where _tt = Tt_39 [] tt_ = Tt_39 instance C_Tt Ent40 Ent30 where _tt = Tt_40 [] tt_ = Tt_40 instance C_Tt Ent41 Ent4 where _tt = Tt_41 [] tt_ = Tt_41 instance C_Tt Ent43 Ent20 where _tt = Tt_43 [] tt_ = Tt_43 instance C_Tt Ent44 Ent30 where _tt = Tt_44 [] tt_ = Tt_44 instance C_Tt Ent45 Ent31 where _tt = Tt_45 [] tt_ = Tt_45 instance C_Tt Ent46 Ent30 where _tt = Tt_46 [] tt_ = Tt_46 instance C_Tt Ent47 Ent30 where _tt = Tt_47 [] tt_ = Tt_47 class C_I a b | a -> b where _i :: [b] -> a i_ :: [Att11] -> [b] -> a instance C_I Ent3 Ent30 where _i = I_3 [] i_ = I_3 instance C_I Ent4 Ent4 where _i = I_4 [] i_ = I_4 instance C_I Ent5 Ent4 where _i = I_5 [] i_ = I_5 instance C_I Ent9 Ent4 where _i = I_9 [] i_ = I_9 instance C_I Ent11 Ent4 where _i = I_11 [] i_ = I_11 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 Ent18 Ent4 where _i = I_18 [] i_ = I_18 instance C_I Ent20 Ent20 where _i = I_20 [] i_ = I_20 instance C_I Ent21 Ent20 where _i = I_21 [] i_ = I_21 instance C_I Ent22 Ent20 where _i = I_22 [] i_ = I_22 instance C_I Ent23 Ent20 where _i = I_23 [] i_ = I_23 instance C_I Ent24 Ent20 where _i = I_24 [] i_ = I_24 instance C_I Ent25 Ent20 where _i = I_25 [] i_ = I_25 instance C_I Ent26 Ent20 where _i = I_26 [] i_ = I_26 instance C_I Ent29 Ent20 where _i = I_29 [] i_ = I_29 instance C_I Ent30 Ent30 where _i = I_30 [] i_ = I_30 instance C_I Ent31 Ent31 where _i = I_31 [] i_ = I_31 instance C_I Ent32 Ent31 where _i = I_32 [] i_ = I_32 instance C_I Ent33 Ent31 where _i = I_33 [] i_ = I_33 instance C_I Ent34 Ent31 where _i = I_34 [] i_ = I_34 instance C_I Ent35 Ent31 where _i = I_35 [] i_ = I_35 instance C_I Ent36 Ent31 where _i = I_36 [] i_ = I_36 instance C_I Ent37 Ent31 where _i = I_37 [] i_ = I_37 instance C_I Ent38 Ent30 where _i = I_38 [] i_ = I_38 instance C_I Ent39 Ent30 where _i = I_39 [] i_ = I_39 instance C_I Ent40 Ent30 where _i = I_40 [] i_ = I_40 instance C_I Ent41 Ent4 where _i = I_41 [] i_ = I_41 instance C_I Ent43 Ent20 where _i = I_43 [] i_ = I_43 instance C_I Ent44 Ent30 where _i = I_44 [] i_ = I_44 instance C_I Ent45 Ent31 where _i = I_45 [] i_ = I_45 instance C_I Ent46 Ent30 where _i = I_46 [] i_ = I_46 instance C_I Ent47 Ent30 where _i = I_47 [] i_ = I_47 class C_B a b | a -> b where _b :: [b] -> a b_ :: [Att11] -> [b] -> a instance C_B Ent3 Ent30 where _b = B_3 [] b_ = B_3 instance C_B Ent4 Ent4 where _b = B_4 [] b_ = B_4 instance C_B Ent5 Ent4 where _b = B_5 [] b_ = B_5 instance C_B Ent9 Ent4 where _b = B_9 [] b_ = B_9 instance C_B Ent11 Ent4 where _b = B_11 [] b_ = B_11 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 Ent18 Ent4 where _b = B_18 [] b_ = B_18 instance C_B Ent20 Ent20 where _b = B_20 [] b_ = B_20 instance C_B Ent21 Ent20 where _b = B_21 [] b_ = B_21 instance C_B Ent22 Ent20 where _b = B_22 [] b_ = B_22 instance C_B Ent23 Ent20 where _b = B_23 [] b_ = B_23 instance C_B Ent24 Ent20 where _b = B_24 [] b_ = B_24 instance C_B Ent25 Ent20 where _b = B_25 [] b_ = B_25 instance C_B Ent26 Ent20 where _b = B_26 [] b_ = B_26 instance C_B Ent29 Ent20 where _b = B_29 [] b_ = B_29 instance C_B Ent30 Ent30 where _b = B_30 [] b_ = B_30 instance C_B Ent31 Ent31 where _b = B_31 [] b_ = B_31 instance C_B Ent32 Ent31 where _b = B_32 [] b_ = B_32 instance C_B Ent33 Ent31 where _b = B_33 [] b_ = B_33 instance C_B Ent34 Ent31 where _b = B_34 [] b_ = B_34 instance C_B Ent35 Ent31 where _b = B_35 [] b_ = B_35 instance C_B Ent36 Ent31 where _b = B_36 [] b_ = B_36 instance C_B Ent37 Ent31 where _b = B_37 [] b_ = B_37 instance C_B Ent38 Ent30 where _b = B_38 [] b_ = B_38 instance C_B Ent39 Ent30 where _b = B_39 [] b_ = B_39 instance C_B Ent40 Ent30 where _b = B_40 [] b_ = B_40 instance C_B Ent41 Ent4 where _b = B_41 [] b_ = B_41 instance C_B Ent43 Ent20 where _b = B_43 [] b_ = B_43 instance C_B Ent44 Ent30 where _b = B_44 [] b_ = B_44 instance C_B Ent45 Ent31 where _b = B_45 [] b_ = B_45 instance C_B Ent46 Ent30 where _b = B_46 [] b_ = B_46 instance C_B Ent47 Ent30 where _b = B_47 [] b_ = B_47 class C_Big a b | a -> b where _big :: [b] -> a big_ :: [Att11] -> [b] -> a instance C_Big Ent3 Ent30 where _big = Big_3 [] big_ = Big_3 instance C_Big Ent4 Ent4 where _big = Big_4 [] big_ = Big_4 instance C_Big Ent5 Ent4 where _big = Big_5 [] big_ = Big_5 instance C_Big Ent9 Ent4 where _big = Big_9 [] big_ = Big_9 instance C_Big Ent11 Ent4 where _big = Big_11 [] big_ = Big_11 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 Ent18 Ent4 where _big = Big_18 [] big_ = Big_18 instance C_Big Ent20 Ent20 where _big = Big_20 [] big_ = Big_20 instance C_Big Ent21 Ent20 where _big = Big_21 [] big_ = Big_21 instance C_Big Ent22 Ent20 where _big = Big_22 [] big_ = Big_22 instance C_Big Ent23 Ent20 where _big = Big_23 [] big_ = Big_23 instance C_Big Ent24 Ent20 where _big = Big_24 [] big_ = Big_24 instance C_Big Ent25 Ent20 where _big = Big_25 [] big_ = Big_25 instance C_Big Ent26 Ent20 where _big = Big_26 [] big_ = Big_26 instance C_Big Ent29 Ent20 where _big = Big_29 [] big_ = Big_29 instance C_Big Ent30 Ent30 where _big = Big_30 [] big_ = Big_30 instance C_Big Ent31 Ent31 where _big = Big_31 [] big_ = Big_31 instance C_Big Ent32 Ent31 where _big = Big_32 [] big_ = Big_32 instance C_Big Ent33 Ent31 where _big = Big_33 [] big_ = Big_33 instance C_Big Ent34 Ent31 where _big = Big_34 [] big_ = Big_34 instance C_Big Ent35 Ent31 where _big = Big_35 [] big_ = Big_35 instance C_Big Ent36 Ent31 where _big = Big_36 [] big_ = Big_36 instance C_Big Ent37 Ent31 where _big = Big_37 [] big_ = Big_37 instance C_Big Ent38 Ent30 where _big = Big_38 [] big_ = Big_38 instance C_Big Ent39 Ent30 where _big = Big_39 [] big_ = Big_39 instance C_Big Ent40 Ent30 where _big = Big_40 [] big_ = Big_40 instance C_Big Ent41 Ent4 where _big = Big_41 [] big_ = Big_41 instance C_Big Ent43 Ent20 where _big = Big_43 [] big_ = Big_43 instance C_Big Ent44 Ent30 where _big = Big_44 [] big_ = Big_44 instance C_Big Ent45 Ent31 where _big = Big_45 [] big_ = Big_45 instance C_Big Ent46 Ent30 where _big = Big_46 [] big_ = Big_46 instance C_Big Ent47 Ent30 where _big = Big_47 [] big_ = Big_47 class C_Small a b | a -> b where _small :: [b] -> a small_ :: [Att11] -> [b] -> a instance C_Small Ent3 Ent30 where _small = Small_3 [] small_ = Small_3 instance C_Small Ent4 Ent4 where _small = Small_4 [] small_ = Small_4 instance C_Small Ent5 Ent4 where _small = Small_5 [] small_ = Small_5 instance C_Small Ent9 Ent4 where _small = Small_9 [] small_ = Small_9 instance C_Small Ent11 Ent4 where _small = Small_11 [] small_ = Small_11 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 Ent18 Ent4 where _small = Small_18 [] small_ = Small_18 instance C_Small Ent20 Ent20 where _small = Small_20 [] small_ = Small_20 instance C_Small Ent21 Ent20 where _small = Small_21 [] small_ = Small_21 instance C_Small Ent22 Ent20 where _small = Small_22 [] small_ = Small_22 instance C_Small Ent23 Ent20 where _small = Small_23 [] small_ = Small_23 instance C_Small Ent24 Ent20 where _small = Small_24 [] small_ = Small_24 instance C_Small Ent25 Ent20 where _small = Small_25 [] small_ = Small_25 instance C_Small Ent26 Ent20 where _small = Small_26 [] small_ = Small_26 instance C_Small Ent29 Ent20 where _small = Small_29 [] small_ = Small_29 instance C_Small Ent30 Ent30 where _small = Small_30 [] small_ = Small_30 instance C_Small Ent31 Ent31 where _small = Small_31 [] small_ = Small_31 instance C_Small Ent32 Ent31 where _small = Small_32 [] small_ = Small_32 instance C_Small Ent33 Ent31 where _small = Small_33 [] small_ = Small_33 instance C_Small Ent34 Ent31 where _small = Small_34 [] small_ = Small_34 instance C_Small Ent35 Ent31 where _small = Small_35 [] small_ = Small_35 instance C_Small Ent36 Ent31 where _small = Small_36 [] small_ = Small_36 instance C_Small Ent37 Ent31 where _small = Small_37 [] small_ = Small_37 instance C_Small Ent38 Ent30 where _small = Small_38 [] small_ = Small_38 instance C_Small Ent39 Ent30 where _small = Small_39 [] small_ = Small_39 instance C_Small Ent40 Ent30 where _small = Small_40 [] small_ = Small_40 instance C_Small Ent41 Ent4 where _small = Small_41 [] small_ = Small_41 instance C_Small Ent43 Ent20 where _small = Small_43 [] small_ = Small_43 instance C_Small Ent44 Ent30 where _small = Small_44 [] small_ = Small_44 instance C_Small Ent45 Ent31 where _small = Small_45 [] small_ = Small_45 instance C_Small Ent46 Ent30 where _small = Small_46 [] small_ = Small_46 instance C_Small Ent47 Ent30 where _small = Small_47 [] small_ = Small_47 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 Ent18 where _object = Object_4 [] object_ = Object_4 instance C_Object Ent5 Ent18 where _object = Object_5 [] object_ = Object_5 instance C_Object Ent11 Ent41 where _object = Object_11 [] object_ = Object_11 instance C_Object Ent12 Ent41 where _object = Object_12 [] object_ = Object_12 instance C_Object Ent17 Ent18 where _object = Object_17 [] object_ = Object_17 instance C_Object Ent18 Ent18 where _object = Object_18 [] object_ = Object_18 instance C_Object Ent20 Ent26 where _object = Object_20 [] object_ = Object_20 instance C_Object Ent21 Ent26 where _object = Object_21 [] object_ = Object_21 instance C_Object Ent23 Ent43 where _object = Object_23 [] object_ = Object_23 instance C_Object Ent24 Ent43 where _object = Object_24 [] object_ = Object_24 instance C_Object Ent25 Ent26 where _object = Object_25 [] object_ = Object_25 instance C_Object Ent26 Ent26 where _object = Object_26 [] object_ = Object_26 instance C_Object Ent29 Ent26 where _object = Object_29 [] object_ = Object_29 instance C_Object Ent30 Ent3 where _object = Object_30 [] object_ = Object_30 instance C_Object Ent31 Ent37 where _object = Object_31 [] object_ = Object_31 instance C_Object Ent32 Ent37 where _object = Object_32 [] object_ = Object_32 instance C_Object Ent34 Ent45 where _object = Object_34 [] object_ = Object_34 instance C_Object Ent35 Ent45 where _object = Object_35 [] object_ = Object_35 instance C_Object Ent36 Ent37 where _object = Object_36 [] object_ = Object_36 instance C_Object Ent37 Ent37 where _object = Object_37 [] object_ = Object_37 instance C_Object Ent38 Ent3 where _object = Object_38 [] object_ = Object_38 instance C_Object Ent40 Ent44 where _object = Object_40 [] object_ = Object_40 instance C_Object Ent41 Ent41 where _object = Object_41 [] object_ = Object_41 instance C_Object Ent43 Ent43 where _object = Object_43 [] object_ = Object_43 instance C_Object Ent44 Ent44 where _object = Object_44 [] object_ = Object_44 instance C_Object Ent45 Ent45 where _object = Object_45 [] object_ = Object_45 instance C_Object Ent46 Ent44 where _object = Object_46 [] object_ = Object_46 instance C_Object Ent47 Ent3 where _object = Object_47 [] object_ = Object_47 class C_Param a where _param :: a param_ :: [Att21] -> a instance C_Param Ent3 where _param = Param_3 [] param_ = Param_3 instance C_Param Ent18 where _param = Param_18 [] param_ = Param_18 instance C_Param Ent26 where _param = Param_26 [] param_ = Param_26 instance C_Param Ent37 where _param = Param_37 [] param_ = Param_37 instance C_Param Ent41 where _param = Param_41 [] param_ = Param_41 instance C_Param Ent43 where _param = Param_43 [] param_ = Param_43 instance C_Param Ent44 where _param = Param_44 [] param_ = Param_44 instance C_Param Ent45 where _param = Param_45 [] param_ = Param_45 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 Ent5 where _img = Img_5 [] img_ = Img_5 instance C_Img Ent11 where _img = Img_11 [] img_ = Img_11 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 Ent18 where _img = Img_18 [] img_ = Img_18 instance C_Img Ent20 where _img = Img_20 [] img_ = Img_20 instance C_Img Ent21 where _img = Img_21 [] img_ = Img_21 instance C_Img Ent23 where _img = Img_23 [] img_ = Img_23 instance C_Img Ent24 where _img = Img_24 [] img_ = Img_24 instance C_Img Ent25 where _img = Img_25 [] img_ = Img_25 instance C_Img Ent26 where _img = Img_26 [] img_ = Img_26 instance C_Img Ent29 where _img = Img_29 [] img_ = Img_29 instance C_Img Ent30 where _img = Img_30 [] img_ = Img_30 instance C_Img Ent31 where _img = Img_31 [] img_ = Img_31 instance C_Img Ent32 where _img = Img_32 [] img_ = Img_32 instance C_Img Ent34 where _img = Img_34 [] img_ = Img_34 instance C_Img Ent35 where _img = Img_35 [] img_ = Img_35 instance C_Img Ent36 where _img = Img_36 [] img_ = Img_36 instance C_Img Ent37 where _img = Img_37 [] img_ = Img_37 instance C_Img Ent38 where _img = Img_38 [] img_ = Img_38 instance C_Img Ent40 where _img = Img_40 [] img_ = Img_40 instance C_Img Ent41 where _img = Img_41 [] img_ = Img_41 instance C_Img Ent43 where _img = Img_43 [] img_ = Img_43 instance C_Img Ent44 where _img = Img_44 [] img_ = Img_44 instance C_Img Ent45 where _img = Img_45 [] img_ = Img_45 instance C_Img Ent46 where _img = Img_46 [] img_ = Img_46 instance C_Img Ent47 where _img = Img_47 [] img_ = Img_47 class C_Map a b | a -> b where _map :: [b] -> a map_ :: [Att25] -> [b] -> a instance C_Map Ent3 Ent19 where _map = Map_3 [] map_ = Map_3 instance C_Map Ent4 Ent19 where _map = Map_4 [] map_ = Map_4 instance C_Map Ent5 Ent19 where _map = Map_5 [] map_ = Map_5 instance C_Map Ent9 Ent19 where _map = Map_9 [] map_ = Map_9 instance C_Map Ent11 Ent42 where _map = Map_11 [] map_ = Map_11 instance C_Map Ent12 Ent42 where _map = Map_12 [] map_ = Map_12 instance C_Map Ent17 Ent19 where _map = Map_17 [] map_ = Map_17 instance C_Map Ent18 Ent19 where _map = Map_18 [] map_ = Map_18 instance C_Map Ent20 Ent19 where _map = Map_20 [] map_ = Map_20 instance C_Map Ent21 Ent19 where _map = Map_21 [] map_ = Map_21 instance C_Map Ent22 Ent19 where _map = Map_22 [] map_ = Map_22 instance C_Map Ent23 Ent42 where _map = Map_23 [] map_ = Map_23 instance C_Map Ent24 Ent42 where _map = Map_24 [] map_ = Map_24 instance C_Map Ent25 Ent19 where _map = Map_25 [] map_ = Map_25 instance C_Map Ent26 Ent19 where _map = Map_26 [] map_ = Map_26 instance C_Map Ent29 Ent19 where _map = Map_29 [] map_ = Map_29 instance C_Map Ent30 Ent19 where _map = Map_30 [] map_ = Map_30 instance C_Map Ent31 Ent19 where _map = Map_31 [] map_ = Map_31 instance C_Map Ent32 Ent19 where _map = Map_32 [] map_ = Map_32 instance C_Map Ent33 Ent19 where _map = Map_33 [] map_ = Map_33 instance C_Map Ent34 Ent42 where _map = Map_34 [] map_ = Map_34 instance C_Map Ent35 Ent42 where _map = Map_35 [] map_ = Map_35 instance C_Map Ent36 Ent19 where _map = Map_36 [] map_ = Map_36 instance C_Map Ent37 Ent19 where _map = Map_37 [] map_ = Map_37 instance C_Map Ent38 Ent19 where _map = Map_38 [] map_ = Map_38 instance C_Map Ent39 Ent19 where _map = Map_39 [] map_ = Map_39 instance C_Map Ent40 Ent42 where _map = Map_40 [] map_ = Map_40 instance C_Map Ent41 Ent42 where _map = Map_41 [] map_ = Map_41 instance C_Map Ent43 Ent42 where _map = Map_43 [] map_ = Map_43 instance C_Map Ent44 Ent42 where _map = Map_44 [] map_ = Map_44 instance C_Map Ent45 Ent42 where _map = Map_45 [] map_ = Map_45 instance C_Map Ent46 Ent42 where _map = Map_46 [] map_ = Map_46 instance C_Map Ent47 Ent19 where _map = Map_47 [] map_ = Map_47 class C_Area a where _area :: a area_ :: [Att27] -> a instance C_Area Ent19 where _area = Area_19 [] area_ = Area_19 instance C_Area Ent42 where _area = Area_42 [] area_ = Area_42 class C_Form a b | a -> b where _form :: [b] -> a form_ :: [Att28] -> [b] -> a instance C_Form Ent3 Ent10 where _form = Form_3 [] form_ = Form_3 instance C_Form Ent5 Ent10 where _form = Form_5 [] form_ = Form_5 instance C_Form Ent6 Ent10 where _form = Form_6 [] form_ = Form_6 instance C_Form Ent17 Ent10 where _form = Form_17 [] form_ = Form_17 instance C_Form Ent18 Ent10 where _form = Form_18 [] form_ = Form_18 instance C_Form Ent19 Ent10 where _form = Form_19 [] form_ = Form_19 instance C_Form Ent21 Ent10 where _form = Form_21 [] form_ = Form_21 instance C_Form Ent25 Ent10 where _form = Form_25 [] form_ = Form_25 instance C_Form Ent26 Ent10 where _form = Form_26 [] form_ = Form_26 instance C_Form Ent32 Ent10 where _form = Form_32 [] form_ = Form_32 instance C_Form Ent36 Ent10 where _form = Form_36 [] form_ = Form_36 instance C_Form Ent37 Ent10 where _form = Form_37 [] form_ = Form_37 instance C_Form Ent38 Ent10 where _form = Form_38 [] form_ = Form_38 instance C_Form Ent47 Ent10 where _form = Form_47 [] form_ = Form_47 class C_Label a b | a -> b where _label :: [b] -> a label_ :: [Att30] -> [b] -> a instance C_Label Ent3 Ent31 where _label = Label_3 [] label_ = Label_3 instance C_Label Ent4 Ent20 where _label = Label_4 [] label_ = Label_4 instance C_Label Ent5 Ent20 where _label = Label_5 [] label_ = Label_5 instance C_Label Ent9 Ent20 where _label = Label_9 [] label_ = Label_9 instance C_Label Ent11 Ent20 where _label = Label_11 [] label_ = Label_11 instance C_Label Ent12 Ent20 where _label = Label_12 [] label_ = Label_12 instance C_Label Ent17 Ent20 where _label = Label_17 [] label_ = Label_17 instance C_Label Ent18 Ent20 where _label = Label_18 [] label_ = Label_18 instance C_Label Ent30 Ent31 where _label = Label_30 [] label_ = Label_30 instance C_Label Ent38 Ent31 where _label = Label_38 [] label_ = Label_38 instance C_Label Ent39 Ent31 where _label = Label_39 [] label_ = Label_39 instance C_Label Ent40 Ent31 where _label = Label_40 [] label_ = Label_40 instance C_Label Ent41 Ent20 where _label = Label_41 [] label_ = Label_41 instance C_Label Ent44 Ent31 where _label = Label_44 [] label_ = Label_44 instance C_Label Ent46 Ent31 where _label = Label_46 [] label_ = Label_46 instance C_Label Ent47 Ent31 where _label = Label_47 [] label_ = Label_47 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 Ent5 where _input = Input_5 [] input_ = Input_5 instance C_Input Ent9 where _input = Input_9 [] input_ = Input_9 instance C_Input Ent11 where _input = Input_11 [] input_ = Input_11 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 Ent18 where _input = Input_18 [] input_ = Input_18 instance C_Input Ent20 where _input = Input_20 [] input_ = Input_20 instance C_Input Ent21 where _input = Input_21 [] input_ = Input_21 instance C_Input Ent22 where _input = Input_22 [] input_ = Input_22 instance C_Input Ent23 where _input = Input_23 [] input_ = Input_23 instance C_Input Ent24 where _input = Input_24 [] input_ = Input_24 instance C_Input Ent25 where _input = Input_25 [] input_ = Input_25 instance C_Input Ent26 where _input = Input_26 [] input_ = Input_26 instance C_Input Ent30 where _input = Input_30 [] input_ = Input_30 instance C_Input Ent31 where _input = Input_31 [] input_ = Input_31 instance C_Input Ent32 where _input = Input_32 [] input_ = Input_32 instance C_Input Ent33 where _input = Input_33 [] input_ = Input_33 instance C_Input Ent34 where _input = Input_34 [] input_ = Input_34 instance C_Input Ent35 where _input = Input_35 [] input_ = Input_35 instance C_Input Ent36 where _input = Input_36 [] input_ = Input_36 instance C_Input Ent37 where _input = Input_37 [] input_ = Input_37 instance C_Input Ent38 where _input = Input_38 [] input_ = Input_38 instance C_Input Ent39 where _input = Input_39 [] input_ = Input_39 instance C_Input Ent40 where _input = Input_40 [] input_ = Input_40 instance C_Input Ent41 where _input = Input_41 [] input_ = Input_41 instance C_Input Ent43 where _input = Input_43 [] input_ = Input_43 instance C_Input Ent44 where _input = Input_44 [] input_ = Input_44 instance C_Input Ent45 where _input = Input_45 [] input_ = Input_45 instance C_Input Ent46 where _input = Input_46 [] input_ = Input_46 instance C_Input Ent47 where _input = Input_47 [] input_ = Input_47 class C_Select a b | a -> b where _select :: [b] -> a select_ :: [Att32] -> [b] -> a instance C_Select Ent3 Ent27 where _select = Select_3 [] select_ = Select_3 instance C_Select Ent4 Ent27 where _select = Select_4 [] select_ = Select_4 instance C_Select Ent5 Ent27 where _select = Select_5 [] select_ = Select_5 instance C_Select Ent9 Ent27 where _select = Select_9 [] select_ = Select_9 instance C_Select Ent11 Ent27 where _select = Select_11 [] select_ = Select_11 instance C_Select Ent12 Ent27 where _select = Select_12 [] select_ = Select_12 instance C_Select Ent17 Ent27 where _select = Select_17 [] select_ = Select_17 instance C_Select Ent18 Ent27 where _select = Select_18 [] select_ = Select_18 instance C_Select Ent20 Ent27 where _select = Select_20 [] select_ = Select_20 instance C_Select Ent21 Ent27 where _select = Select_21 [] select_ = Select_21 instance C_Select Ent22 Ent27 where _select = Select_22 [] select_ = Select_22 instance C_Select Ent23 Ent27 where _select = Select_23 [] select_ = Select_23 instance C_Select Ent24 Ent27 where _select = Select_24 [] select_ = Select_24 instance C_Select Ent25 Ent27 where _select = Select_25 [] select_ = Select_25 instance C_Select Ent26 Ent27 where _select = Select_26 [] select_ = Select_26 instance C_Select Ent30 Ent27 where _select = Select_30 [] select_ = Select_30 instance C_Select Ent31 Ent27 where _select = Select_31 [] select_ = Select_31 instance C_Select Ent32 Ent27 where _select = Select_32 [] select_ = Select_32 instance C_Select Ent33 Ent27 where _select = Select_33 [] select_ = Select_33 instance C_Select Ent34 Ent27 where _select = Select_34 [] select_ = Select_34 instance C_Select Ent35 Ent27 where _select = Select_35 [] select_ = Select_35 instance C_Select Ent36 Ent27 where _select = Select_36 [] select_ = Select_36 instance C_Select Ent37 Ent27 where _select = Select_37 [] select_ = Select_37 instance C_Select Ent38 Ent27 where _select = Select_38 [] select_ = Select_38 instance C_Select Ent39 Ent27 where _select = Select_39 [] select_ = Select_39 instance C_Select Ent40 Ent27 where _select = Select_40 [] select_ = Select_40 instance C_Select Ent41 Ent27 where _select = Select_41 [] select_ = Select_41 instance C_Select Ent43 Ent27 where _select = Select_43 [] select_ = Select_43 instance C_Select Ent44 Ent27 where _select = Select_44 [] select_ = Select_44 instance C_Select Ent45 Ent27 where _select = Select_45 [] select_ = Select_45 instance C_Select Ent46 Ent27 where _select = Select_46 [] select_ = Select_46 instance C_Select Ent47 Ent27 where _select = Select_47 [] select_ = Select_47 class C_Optgroup a b | a -> b where _optgroup :: [b] -> a optgroup_ :: [Att33] -> [b] -> a instance C_Optgroup Ent27 Ent28 where _optgroup = Optgroup_27 [] optgroup_ = Optgroup_27 class C_Option a b | a -> b where _option :: [b] -> a option_ :: [Att35] -> [b] -> a instance C_Option Ent27 Ent2 where _option = Option_27 [] option_ = Option_27 instance C_Option Ent28 Ent2 where _option = Option_28 [] option_ = Option_28 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 Ent2 where _textarea = Textarea_4 [] textarea_ = Textarea_4 instance C_Textarea Ent5 Ent2 where _textarea = Textarea_5 [] textarea_ = Textarea_5 instance C_Textarea Ent9 Ent2 where _textarea = Textarea_9 [] textarea_ = Textarea_9 instance C_Textarea Ent11 Ent2 where _textarea = Textarea_11 [] textarea_ = Textarea_11 instance C_Textarea Ent12 Ent2 where _textarea = Textarea_12 [] textarea_ = Textarea_12 instance C_Textarea Ent17 Ent2 where _textarea = Textarea_17 [] textarea_ = Textarea_17 instance C_Textarea Ent18 Ent2 where _textarea = Textarea_18 [] textarea_ = Textarea_18 instance C_Textarea Ent20 Ent2 where _textarea = Textarea_20 [] textarea_ = Textarea_20 instance C_Textarea Ent21 Ent2 where _textarea = Textarea_21 [] textarea_ = Textarea_21 instance C_Textarea Ent22 Ent2 where _textarea = Textarea_22 [] textarea_ = Textarea_22 instance C_Textarea Ent23 Ent2 where _textarea = Textarea_23 [] textarea_ = Textarea_23 instance C_Textarea Ent24 Ent2 where _textarea = Textarea_24 [] textarea_ = Textarea_24 instance C_Textarea Ent25 Ent2 where _textarea = Textarea_25 [] textarea_ = Textarea_25 instance C_Textarea Ent26 Ent2 where _textarea = Textarea_26 [] textarea_ = Textarea_26 instance C_Textarea Ent30 Ent2 where _textarea = Textarea_30 [] textarea_ = Textarea_30 instance C_Textarea Ent31 Ent2 where _textarea = Textarea_31 [] textarea_ = Textarea_31 instance C_Textarea Ent32 Ent2 where _textarea = Textarea_32 [] textarea_ = Textarea_32 instance C_Textarea Ent33 Ent2 where _textarea = Textarea_33 [] textarea_ = Textarea_33 instance C_Textarea Ent34 Ent2 where _textarea = Textarea_34 [] textarea_ = Textarea_34 instance C_Textarea Ent35 Ent2 where _textarea = Textarea_35 [] textarea_ = Textarea_35 instance C_Textarea Ent36 Ent2 where _textarea = Textarea_36 [] textarea_ = Textarea_36 instance C_Textarea Ent37 Ent2 where _textarea = Textarea_37 [] textarea_ = Textarea_37 instance C_Textarea Ent38 Ent2 where _textarea = Textarea_38 [] textarea_ = Textarea_38 instance C_Textarea Ent39 Ent2 where _textarea = Textarea_39 [] textarea_ = Textarea_39 instance C_Textarea Ent40 Ent2 where _textarea = Textarea_40 [] textarea_ = Textarea_40 instance C_Textarea Ent41 Ent2 where _textarea = Textarea_41 [] textarea_ = Textarea_41 instance C_Textarea Ent43 Ent2 where _textarea = Textarea_43 [] textarea_ = Textarea_43 instance C_Textarea Ent44 Ent2 where _textarea = Textarea_44 [] textarea_ = Textarea_44 instance C_Textarea Ent45 Ent2 where _textarea = Textarea_45 [] textarea_ = Textarea_45 instance C_Textarea Ent46 Ent2 where _textarea = Textarea_46 [] textarea_ = Textarea_46 instance C_Textarea Ent47 Ent2 where _textarea = Textarea_47 [] textarea_ = Textarea_47 class C_Fieldset a b | a -> b where _fieldset :: [b] -> a fieldset_ :: [Att11] -> [b] -> a instance C_Fieldset Ent3 Ent47 where _fieldset = Fieldset_3 [] fieldset_ = Fieldset_3 instance C_Fieldset Ent5 Ent17 where _fieldset = Fieldset_5 [] fieldset_ = Fieldset_5 instance C_Fieldset Ent6 Ent17 where _fieldset = Fieldset_6 [] fieldset_ = Fieldset_6 instance C_Fieldset Ent10 Ent12 where _fieldset = Fieldset_10 [] fieldset_ = Fieldset_10 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 Ent17 where _fieldset = Fieldset_17 [] fieldset_ = Fieldset_17 instance C_Fieldset Ent18 Ent17 where _fieldset = Fieldset_18 [] fieldset_ = Fieldset_18 instance C_Fieldset Ent19 Ent17 where _fieldset = Fieldset_19 [] fieldset_ = Fieldset_19 instance C_Fieldset Ent21 Ent25 where _fieldset = Fieldset_21 [] fieldset_ = Fieldset_21 instance C_Fieldset Ent23 Ent24 where _fieldset = Fieldset_23 [] fieldset_ = Fieldset_23 instance C_Fieldset Ent24 Ent24 where _fieldset = Fieldset_24 [] fieldset_ = Fieldset_24 instance C_Fieldset Ent25 Ent25 where _fieldset = Fieldset_25 [] fieldset_ = Fieldset_25 instance C_Fieldset Ent26 Ent25 where _fieldset = Fieldset_26 [] fieldset_ = Fieldset_26 instance C_Fieldset Ent32 Ent36 where _fieldset = Fieldset_32 [] fieldset_ = Fieldset_32 instance C_Fieldset Ent34 Ent35 where _fieldset = Fieldset_34 [] fieldset_ = Fieldset_34 instance C_Fieldset Ent35 Ent35 where _fieldset = Fieldset_35 [] fieldset_ = Fieldset_35 instance C_Fieldset Ent36 Ent36 where _fieldset = Fieldset_36 [] fieldset_ = Fieldset_36 instance C_Fieldset Ent37 Ent36 where _fieldset = Fieldset_37 [] fieldset_ = Fieldset_37 instance C_Fieldset Ent38 Ent47 where _fieldset = Fieldset_38 [] fieldset_ = Fieldset_38 instance C_Fieldset Ent40 Ent46 where _fieldset = Fieldset_40 [] fieldset_ = Fieldset_40 instance C_Fieldset Ent41 Ent12 where _fieldset = Fieldset_41 [] fieldset_ = Fieldset_41 instance C_Fieldset Ent42 Ent12 where _fieldset = Fieldset_42 [] fieldset_ = Fieldset_42 instance C_Fieldset Ent43 Ent24 where _fieldset = Fieldset_43 [] fieldset_ = Fieldset_43 instance C_Fieldset Ent44 Ent46 where _fieldset = Fieldset_44 [] fieldset_ = Fieldset_44 instance C_Fieldset Ent45 Ent35 where _fieldset = Fieldset_45 [] fieldset_ = Fieldset_45 instance C_Fieldset Ent46 Ent46 where _fieldset = Fieldset_46 [] fieldset_ = Fieldset_46 instance C_Fieldset Ent47 Ent47 where _fieldset = Fieldset_47 [] fieldset_ = Fieldset_47 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 Ent17 Ent4 where _legend = Legend_17 [] legend_ = Legend_17 instance C_Legend Ent24 Ent20 where _legend = Legend_24 [] legend_ = Legend_24 instance C_Legend Ent25 Ent20 where _legend = Legend_25 [] legend_ = Legend_25 instance C_Legend Ent35 Ent31 where _legend = Legend_35 [] legend_ = Legend_35 instance C_Legend Ent36 Ent31 where _legend = Legend_36 [] legend_ = Legend_36 instance C_Legend Ent46 Ent30 where _legend = Legend_46 [] legend_ = Legend_46 instance C_Legend Ent47 Ent30 where _legend = Legend_47 [] legend_ = Legend_47 class C_Button a b | a -> b where _button :: [b] -> a button_ :: [Att40] -> [b] -> a instance C_Button Ent3 Ent29 where _button = Button_3 [] button_ = Button_3 instance C_Button Ent4 Ent29 where _button = Button_4 [] button_ = Button_4 instance C_Button Ent5 Ent29 where _button = Button_5 [] button_ = Button_5 instance C_Button Ent9 Ent29 where _button = Button_9 [] button_ = Button_9 instance C_Button Ent11 Ent29 where _button = Button_11 [] button_ = Button_11 instance C_Button Ent12 Ent29 where _button = Button_12 [] button_ = Button_12 instance C_Button Ent17 Ent29 where _button = Button_17 [] button_ = Button_17 instance C_Button Ent18 Ent29 where _button = Button_18 [] button_ = Button_18 instance C_Button Ent20 Ent29 where _button = Button_20 [] button_ = Button_20 instance C_Button Ent21 Ent29 where _button = Button_21 [] button_ = Button_21 instance C_Button Ent22 Ent29 where _button = Button_22 [] button_ = Button_22 instance C_Button Ent23 Ent29 where _button = Button_23 [] button_ = Button_23 instance C_Button Ent24 Ent29 where _button = Button_24 [] button_ = Button_24 instance C_Button Ent25 Ent29 where _button = Button_25 [] button_ = Button_25 instance C_Button Ent26 Ent29 where _button = Button_26 [] button_ = Button_26 instance C_Button Ent30 Ent29 where _button = Button_30 [] button_ = Button_30 instance C_Button Ent31 Ent29 where _button = Button_31 [] button_ = Button_31 instance C_Button Ent32 Ent29 where _button = Button_32 [] button_ = Button_32 instance C_Button Ent33 Ent29 where _button = Button_33 [] button_ = Button_33 instance C_Button Ent34 Ent29 where _button = Button_34 [] button_ = Button_34 instance C_Button Ent35 Ent29 where _button = Button_35 [] button_ = Button_35 instance C_Button Ent36 Ent29 where _button = Button_36 [] button_ = Button_36 instance C_Button Ent37 Ent29 where _button = Button_37 [] button_ = Button_37 instance C_Button Ent38 Ent29 where _button = Button_38 [] button_ = Button_38 instance C_Button Ent39 Ent29 where _button = Button_39 [] button_ = Button_39 instance C_Button Ent40 Ent29 where _button = Button_40 [] button_ = Button_40 instance C_Button Ent41 Ent29 where _button = Button_41 [] button_ = Button_41 instance C_Button Ent43 Ent29 where _button = Button_43 [] button_ = Button_43 instance C_Button Ent44 Ent29 where _button = Button_44 [] button_ = Button_44 instance C_Button Ent45 Ent29 where _button = Button_45 [] button_ = Button_45 instance C_Button Ent46 Ent29 where _button = Button_46 [] button_ = Button_46 instance C_Button Ent47 Ent29 where _button = Button_47 [] button_ = Button_47 class C_Table a b | a -> b where _table :: [b] -> a table_ :: [Att41] -> [b] -> a instance C_Table Ent3 Ent13 where _table = Table_3 [] table_ = Table_3 instance C_Table Ent5 Ent13 where _table = Table_5 [] table_ = Table_5 instance C_Table Ent6 Ent13 where _table = Table_6 [] table_ = Table_6 instance C_Table Ent10 Ent13 where _table = Table_10 [] table_ = Table_10 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 Ent19 Ent13 where _table = Table_19 [] table_ = Table_19 instance C_Table Ent21 Ent13 where _table = Table_21 [] table_ = Table_21 instance C_Table Ent23 Ent13 where _table = Table_23 [] table_ = Table_23 instance C_Table Ent24 Ent13 where _table = Table_24 [] table_ = Table_24 instance C_Table Ent25 Ent13 where _table = Table_25 [] table_ = Table_25 instance C_Table Ent26 Ent13 where _table = Table_26 [] table_ = Table_26 instance C_Table Ent29 Ent13 where _table = Table_29 [] table_ = Table_29 instance C_Table Ent32 Ent13 where _table = Table_32 [] table_ = Table_32 instance C_Table Ent34 Ent13 where _table = Table_34 [] table_ = Table_34 instance C_Table Ent35 Ent13 where _table = Table_35 [] table_ = Table_35 instance C_Table Ent36 Ent13 where _table = Table_36 [] table_ = Table_36 instance C_Table Ent37 Ent13 where _table = Table_37 [] table_ = Table_37 instance C_Table Ent38 Ent13 where _table = Table_38 [] table_ = Table_38 instance C_Table Ent40 Ent13 where _table = Table_40 [] table_ = Table_40 instance C_Table Ent41 Ent13 where _table = Table_41 [] table_ = Table_41 instance C_Table Ent42 Ent13 where _table = Table_42 [] table_ = Table_42 instance C_Table Ent43 Ent13 where _table = Table_43 [] table_ = Table_43 instance C_Table Ent44 Ent13 where _table = Table_44 [] table_ = Table_44 instance C_Table Ent45 Ent13 where _table = Table_45 [] table_ = Table_45 instance C_Table Ent46 Ent13 where _table = Table_46 [] table_ = Table_46 instance C_Table Ent47 Ent13 where _table = Table_47 [] table_ = Table_47 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 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 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 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 class C_Colgroup a b | a -> b where _colgroup :: [b] -> a colgroup_ :: [Att43] -> [b] -> a instance C_Colgroup Ent13 Ent15 where _colgroup = Colgroup_13 [] colgroup_ = Colgroup_13 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 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 class C_Th a b | a -> b where _th :: [b] -> a th_ :: [Att44] -> [b] -> a instance C_Th Ent16 Ent11 where _th = Th_16 [] th_ = Th_16 class C_Td a b | a -> b where _td :: [b] -> a td_ :: [Att44] -> [b] -> a instance C_Td Ent16 Ent11 where _td = Td_16 [] td_ = Td_16 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 Ent9 where pcdata s = PCDATA_9 [] (s2b_escape s) pcdata_bs = PCDATA_9 [] instance C_PCDATA Ent11 where pcdata s = PCDATA_11 [] (s2b_escape s) pcdata_bs = PCDATA_11 [] 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 Ent18 where pcdata s = PCDATA_18 [] (s2b_escape s) pcdata_bs = PCDATA_18 [] instance C_PCDATA Ent20 where pcdata s = PCDATA_20 [] (s2b_escape s) pcdata_bs = PCDATA_20 [] 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 Ent23 where pcdata s = PCDATA_23 [] (s2b_escape s) pcdata_bs = PCDATA_23 [] instance C_PCDATA Ent24 where pcdata s = PCDATA_24 [] (s2b_escape s) pcdata_bs = PCDATA_24 [] instance C_PCDATA Ent25 where pcdata s = PCDATA_25 [] (s2b_escape s) pcdata_bs = PCDATA_25 [] instance C_PCDATA Ent26 where pcdata s = PCDATA_26 [] (s2b_escape s) pcdata_bs = PCDATA_26 [] instance C_PCDATA Ent29 where pcdata s = PCDATA_29 [] (s2b_escape s) pcdata_bs = PCDATA_29 [] instance C_PCDATA Ent30 where pcdata s = PCDATA_30 [] (s2b_escape s) pcdata_bs = PCDATA_30 [] instance C_PCDATA Ent31 where pcdata s = PCDATA_31 [] (s2b_escape s) pcdata_bs = PCDATA_31 [] instance C_PCDATA Ent32 where pcdata s = PCDATA_32 [] (s2b_escape s) pcdata_bs = PCDATA_32 [] instance C_PCDATA Ent33 where pcdata s = PCDATA_33 [] (s2b_escape s) pcdata_bs = PCDATA_33 [] instance C_PCDATA Ent34 where pcdata s = PCDATA_34 [] (s2b_escape s) pcdata_bs = PCDATA_34 [] instance C_PCDATA Ent35 where pcdata s = PCDATA_35 [] (s2b_escape s) pcdata_bs = PCDATA_35 [] instance C_PCDATA Ent36 where pcdata s = PCDATA_36 [] (s2b_escape s) pcdata_bs = PCDATA_36 [] instance C_PCDATA Ent37 where pcdata s = PCDATA_37 [] (s2b_escape s) pcdata_bs = PCDATA_37 [] instance C_PCDATA Ent38 where pcdata s = PCDATA_38 [] (s2b_escape s) pcdata_bs = PCDATA_38 [] instance C_PCDATA Ent39 where pcdata s = PCDATA_39 [] (s2b_escape s) pcdata_bs = PCDATA_39 [] instance C_PCDATA Ent40 where pcdata s = PCDATA_40 [] (s2b_escape s) pcdata_bs = PCDATA_40 [] instance C_PCDATA Ent41 where pcdata s = PCDATA_41 [] (s2b_escape s) pcdata_bs = PCDATA_41 [] instance C_PCDATA Ent43 where pcdata s = PCDATA_43 [] (s2b_escape s) pcdata_bs = PCDATA_43 [] instance C_PCDATA Ent44 where pcdata s = PCDATA_44 [] (s2b_escape s) pcdata_bs = PCDATA_44 [] instance C_PCDATA Ent45 where pcdata s = PCDATA_45 [] (s2b_escape s) pcdata_bs = PCDATA_45 [] instance C_PCDATA Ent46 where pcdata s = PCDATA_46 [] (s2b_escape s) pcdata_bs = PCDATA_46 [] instance C_PCDATA Ent47 where pcdata s = PCDATA_47 [] (s2b_escape s) pcdata_bs = PCDATA_47 [] 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 (Script_5 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_5 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_5 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_5 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_5 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_5 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_5 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_5 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_5 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_5 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_5 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_5 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_5 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_5 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_5 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_5 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_5 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_5 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_5 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_5 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_5 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_5 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_5 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_5 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_5 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_5 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_5 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_5 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_5 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_5 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_5 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_5 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_5 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_5 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_5 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_5 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_5 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_5 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_5 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_5 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_5 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_5 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_5 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_5 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_5 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_5 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_5 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_5 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_5 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_5 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_5 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] 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 (Form_6 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_6 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_6 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent7 where render_bs (Li_7 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e] instance Render Ent8 where render_bs (Dt_8 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e] render_bs (Dd_8 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e] instance Render Ent9 where render_bs (Script_9 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_9 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_9 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_9 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_9 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_9 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_9 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_9 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_9 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_9 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_9 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_9 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_9 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_9 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_9 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_9 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_9 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_9 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_9 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_9 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_9 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_9 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_9 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_9 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Map_9 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_9 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_9 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_9 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_9 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_9 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_9 _ str) = str 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 (Noscript_10 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_10 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_10 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_10 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_10 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_10 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_10 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_10 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_10 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_10 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_10 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_10 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_10 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_10 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_10 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_10 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_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 (Fieldset_10 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_10 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] 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 (Span_11 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_11 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_11 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_11 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_11 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_11 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_11 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_11 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_11 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_11 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_11 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_11 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_11 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_11 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_11 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_11 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_11 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_11 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_11 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_11 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_11 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_11 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_11 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_11 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_11 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_11 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_11 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_11 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_11 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_11 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_11 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_11 _ str) = str 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 (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 (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 (Legend_17 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_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 (Span_18 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_18 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_18 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_18 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_18 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_18 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_18 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_18 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_18 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_18 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_18 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_18 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_18 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_18 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_18 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_18 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_18 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_18 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_18 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_18 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_18 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_18 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_18 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_18 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_18 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_18 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_18 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_18 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_18 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_18 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_18 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_18 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_18 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_18 _ str) = str instance Render Ent19 where render_bs (Script_19 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_19 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_19 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_19 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_19 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_19 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_19 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_19 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_19 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_19 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_19 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_19 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_19 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_19 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_19 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_19 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_19 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_19 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_19 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Area_19 att) = B.concat [area_byte_b,renderAtts att,gts_byte] render_bs (Form_19 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_19 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_19 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent20 where render_bs (Script_20 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_20 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_20 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_20 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_20 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_20 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_20 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_20 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_20 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_20 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_20 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_20 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_20 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_20 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_20 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_20 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_20 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_20 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_20 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_20 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_20 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_20 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_20 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_20 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_20 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_20 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_20 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_20 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_20 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_20 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_20 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_20 _ str) = str 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 (Form_21 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_21 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_21 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_21 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_21 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_21 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_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 (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 (Map_22 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_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 (Span_23 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_23 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_23 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_23 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_23 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_23 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_23 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_23 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_23 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_23 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_23 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_23 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_23 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_23 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_23 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_23 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_23 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_23 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_23 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_23 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_23 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_23 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_23 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_23 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_23 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_23 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_23 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_23 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_23 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_23 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_23 _ str) = str instance Render Ent24 where render_bs (Script_24 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_24 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_24 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_24 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_24 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_24 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_24 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_24 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_24 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_24 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_24 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_24 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_24 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_24 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_24 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_24 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_24 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_24 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_24 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_24 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_24 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_24 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_24 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_24 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_24 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_24 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_24 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_24 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_24 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_24 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_24 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_24 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_24 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_24 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_24 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_24 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_24 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_24 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_24 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_24 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_24 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_24 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_24 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_24 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_24 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_24 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_24 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_24 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_24 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_24 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_24 _ str) = str instance Render Ent25 where render_bs (Script_25 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_25 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_25 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_25 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_25 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_25 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_25 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_25 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_25 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_25 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_25 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_25 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_25 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_25 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_25 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_25 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_25 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_25 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_25 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_25 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_25 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_25 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_25 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_25 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_25 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_25 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_25 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_25 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_25 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_25 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_25 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_25 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_25 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_25 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_25 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_25 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_25 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_25 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_25 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_25 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_25 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_25 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_25 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_25 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_25 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_25 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_25 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_25 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_25 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_25 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_25 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_25 _ str) = str 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 (Param_26 att) = B.concat [param_byte_b,renderAtts att,gts_byte] 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 (Form_26 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_26 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_26 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_26 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_26 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_26 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_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 (Optgroup_27 att c) = B.concat [optgroup_byte_b,renderAtts att,gt_byte, maprender c,optgroup_byte_e] render_bs (Option_27 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent28 where render_bs (Option_28 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent29 where render_bs (Script_29 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_29 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_29 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_29 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_29 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_29 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_29 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_29 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_29 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_29 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_29 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_29 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_29 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_29 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_29 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_29 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_29 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_29 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_29 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_29 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_29 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_29 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_29 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_29 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_29 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_29 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_29 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_29 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_29 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_29 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_29 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_29 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_29 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_29 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_29 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_29 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_29 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_29 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_29 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_29 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_29 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_29 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_29 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Table_29 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_29 _ str) = str instance Render Ent30 where render_bs (Script_30 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_30 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_30 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_30 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_30 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_30 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_30 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_30 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_30 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_30 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_30 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_30 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_30 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_30 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_30 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_30 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_30 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_30 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_30 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_30 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_30 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_30 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_30 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_30 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_30 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_30 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_30 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_30 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_30 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_30 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_30 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_30 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_30 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_30 _ str) = str 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 (Object_31 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_31 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_31 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_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 (A_32 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_32 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_32 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_32 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_32 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_32 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_32 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_32 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_32 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_32 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_32 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_32 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_32 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_32 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_32 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_32 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_32 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_32 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_32 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_32 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_32 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_32 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_32 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_32 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_32 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_32 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_32 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_32 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_32 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_32 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_32 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_32 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_32 _ str) = str 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 (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 (Map_33 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_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 (Button_33 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_33 _ str) = str instance Render Ent34 where render_bs (Script_34 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_34 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_34 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_34 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_34 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_34 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_34 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_34 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_34 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_34 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_34 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_34 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_34 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_34 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_34 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_34 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_34 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_34 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_34 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_34 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_34 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_34 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_34 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_34 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_34 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_34 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_34 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_34 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_34 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_34 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_34 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_34 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_34 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_34 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_34 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_34 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_34 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_34 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_34 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_34 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_34 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_34 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_34 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_34 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_34 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_34 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_34 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_34 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_34 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_34 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_34 _ str) = str instance Render Ent35 where render_bs (Script_35 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_35 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_35 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_35 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_35 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_35 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_35 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_35 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_35 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_35 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_35 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_35 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_35 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_35 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_35 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_35 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_35 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_35 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_35 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_35 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_35 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_35 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_35 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_35 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_35 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_35 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_35 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_35 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_35 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_35 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_35 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_35 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_35 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_35 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_35 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_35 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_35 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_35 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_35 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_35 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_35 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_35 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_35 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_35 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_35 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_35 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_35 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_35 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_35 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_35 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_35 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_35 _ str) = str instance Render Ent36 where render_bs (Script_36 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_36 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_36 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_36 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_36 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_36 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_36 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_36 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_36 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_36 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_36 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_36 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_36 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_36 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_36 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_36 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_36 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_36 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_36 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_36 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_36 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_36 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_36 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_36 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_36 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_36 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_36 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_36 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_36 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_36 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_36 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_36 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_36 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_36 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_36 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_36 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_36 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_36 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_36 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_36 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_36 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_36 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_36 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_36 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_36 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_36 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_36 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_36 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_36 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_36 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_36 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_36 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_36 _ str) = str instance Render Ent37 where render_bs (Script_37 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_37 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_37 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_37 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_37 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_37 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_37 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_37 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_37 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_37 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_37 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_37 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_37 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_37 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_37 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_37 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_37 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_37 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_37 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_37 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_37 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_37 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_37 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_37 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_37 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_37 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_37 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_37 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_37 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_37 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_37 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_37 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_37 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_37 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_37 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_37 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_37 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_37 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_37 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_37 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_37 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_37 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_37 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_37 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_37 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_37 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_37 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_37 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_37 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_37 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_37 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_37 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_37 _ str) = str instance Render Ent38 where render_bs (Script_38 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_38 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_38 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_38 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_38 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_38 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_38 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_38 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_38 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_38 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_38 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_38 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_38 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_38 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_38 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_38 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_38 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_38 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_38 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_38 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_38 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_38 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_38 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_38 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_38 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_38 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_38 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_38 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_38 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_38 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_38 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_38 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_38 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_38 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_38 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_38 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_38 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_38 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_38 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_38 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_38 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_38 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_38 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_38 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_38 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_38 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_38 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_38 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_38 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_38 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_38 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_38 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_38 _ str) = str instance Render Ent39 where render_bs (Script_39 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_39 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_39 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_39 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_39 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_39 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_39 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_39 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_39 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_39 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_39 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_39 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_39 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_39 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_39 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_39 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_39 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_39 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_39 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_39 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_39 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_39 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_39 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_39 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_39 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Map_39 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_39 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_39 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_39 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_39 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_39 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_39 _ str) = str instance Render Ent40 where render_bs (Script_40 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_40 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_40 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_40 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_40 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_40 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_40 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_40 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_40 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_40 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_40 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_40 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_40 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_40 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_40 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_40 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_40 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_40 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_40 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_40 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_40 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_40 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_40 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_40 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_40 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_40 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_40 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_40 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_40 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_40 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_40 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_40 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_40 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_40 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_40 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_40 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_40 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_40 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_40 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_40 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_40 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_40 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_40 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_40 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_40 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_40 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_40 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_40 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_40 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_40 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_40 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_40 _ str) = str instance Render Ent41 where render_bs (Script_41 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_41 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_41 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_41 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_41 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_41 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_41 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_41 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_41 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_41 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_41 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_41 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_41 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_41 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_41 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_41 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_41 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_41 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_41 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_41 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_41 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_41 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_41 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_41 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_41 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_41 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_41 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_41 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_41 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_41 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_41 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_41 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_41 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_41 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_41 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_41 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_41 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_41 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_41 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_41 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_41 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_41 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_41 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_41 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_41 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_41 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_41 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_41 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_41 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_41 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_41 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_41 _ str) = str instance Render Ent42 where render_bs (Script_42 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_42 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_42 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_42 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_42 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_42 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_42 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_42 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_42 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_42 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_42 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_42 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_42 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_42 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_42 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_42 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_42 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_42 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_42 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Area_42 att) = B.concat [area_byte_b,renderAtts att,gts_byte] render_bs (Fieldset_42 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Table_42 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] instance Render Ent43 where render_bs (Script_43 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_43 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_43 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_43 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_43 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_43 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_43 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_43 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_43 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_43 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_43 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_43 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_43 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_43 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_43 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_43 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_43 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_43 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_43 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_43 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_43 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_43 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_43 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_43 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_43 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_43 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_43 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_43 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_43 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_43 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_43 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_43 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_43 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_43 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_43 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_43 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_43 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_43 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_43 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_43 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_43 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_43 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_43 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_43 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_43 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_43 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_43 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_43 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_43 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_43 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_43 _ str) = str instance Render Ent44 where render_bs (Script_44 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_44 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_44 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_44 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_44 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_44 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_44 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_44 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_44 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_44 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_44 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_44 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_44 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_44 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_44 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_44 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_44 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_44 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_44 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_44 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_44 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_44 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_44 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_44 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_44 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_44 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_44 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_44 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_44 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_44 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_44 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_44 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_44 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_44 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_44 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_44 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_44 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_44 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_44 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_44 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_44 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_44 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_44 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_44 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_44 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_44 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_44 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_44 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_44 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_44 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_44 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_44 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_44 _ str) = str instance Render Ent45 where render_bs (Script_45 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_45 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_45 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_45 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_45 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_45 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_45 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_45 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_45 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_45 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_45 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_45 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_45 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_45 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_45 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_45 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_45 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_45 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_45 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_45 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_45 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_45 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_45 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_45 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_45 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_45 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_45 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_45 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_45 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_45 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_45 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_45 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_45 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_45 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_45 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_45 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_45 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_45 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_45 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_45 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_45 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_45 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_45 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Img_45 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_45 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_45 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_45 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_45 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_45 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_45 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_45 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_45 _ str) = str instance Render Ent46 where render_bs (Script_46 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_46 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_46 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_46 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_46 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_46 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_46 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_46 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_46 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_46 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_46 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_46 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_46 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_46 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_46 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_46 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_46 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_46 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_46 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_46 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_46 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_46 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_46 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_46 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_46 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_46 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_46 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_46 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_46 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_46 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_46 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_46 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_46 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_46 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_46 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_46 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_46 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_46 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_46 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_46 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_46 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_46 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_46 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_46 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_46 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_46 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_46 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_46 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_46 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_46 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_46 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_46 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_46 _ str) = str instance Render Ent47 where render_bs (Script_47 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_47 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_47 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_47 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_47 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_47 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_47 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_47 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_47 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_47 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_47 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_47 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Dl_47 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_47 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_47 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_47 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_47 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Ins_47 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_47 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_47 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_47 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_47 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_47 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_47 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_47 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_47 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_47 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_47 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_47 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_47 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_47 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_47 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_47 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_47 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_47 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_47 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_47 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_47 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_47 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_47 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_47 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (Object_47 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Img_47 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_47 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_47 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_47 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_47 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_47 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_47 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_47 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_47 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_47 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Table_47 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_47 _ str) = str 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" class TagStr a where tagStr :: a -> String instance TagStr Ent where tagStr (Html att c) = "html" instance TagStr Ent0 where tagStr (Head_0 _ _) = "head" tagStr (Body_0 _ _) = "body" instance TagStr Ent1 where tagStr (Title_1 _ _) = "title" tagStr (Base_1 _) = "base" tagStr (Meta_1 _) = "meta" tagStr (Link_1 _) = "link" tagStr (Style_1 _ _) = "style" tagStr (Script_1 _ _) = "script" tagStr (Object_1 _ _) = "object" instance TagStr Ent2 where tagStr (PCDATA_2 _ _) = "PCDATA" instance TagStr Ent3 where tagStr (Script_3 _ _) = "script" tagStr (Noscript_3 _ _) = "noscript" tagStr (Div_3 _ _) = "div" tagStr (P_3 _ _) = "p" tagStr (H1_3 _ _) = "h1" tagStr (H2_3 _ _) = "h2" tagStr (H3_3 _ _) = "h3" tagStr (H4_3 _ _) = "h4" tagStr (H5_3 _ _) = "h5" tagStr (H6_3 _ _) = "h6" tagStr (Ul_3 _ _) = "ul" tagStr (Ol_3 _ _) = "ol" tagStr (Dl_3 _ _) = "dl" tagStr (Address_3 _ _) = "address" tagStr (Hr_3 _) = "hr" tagStr (Pre_3 _ _) = "pre" tagStr (Blockquote_3 _ _) = "blockquote" tagStr (Ins_3 _ _) = "ins" tagStr (Del_3 _ _) = "del" tagStr (A_3 _ _) = "a" tagStr (Span_3 _ _) = "span" tagStr (Bdo_3 _ _) = "bdo" tagStr (Br_3 _) = "br" tagStr (Em_3 _ _) = "em" tagStr (Strong_3 _ _) = "strong" tagStr (Dfn_3 _ _) = "dfn" tagStr (Code_3 _ _) = "code" tagStr (Samp_3 _ _) = "samp" tagStr (Kbd_3 _ _) = "kbd" tagStr (Var_3 _ _) = "var" tagStr (Cite_3 _ _) = "cite" tagStr (Abbr_3 _ _) = "abbr" tagStr (Acronym_3 _ _) = "acronym" tagStr (Q_3 _ _) = "q" tagStr (Sub_3 _ _) = "sub" tagStr (Sup_3 _ _) = "sup" tagStr (Tt_3 _ _) = "tt" tagStr (I_3 _ _) = "i" tagStr (B_3 _ _) = "b" tagStr (Big_3 _ _) = "big" tagStr (Small_3 _ _) = "small" tagStr (Object_3 _ _) = "object" tagStr (Param_3 _) = "param" tagStr (Img_3 _) = "img" tagStr (Map_3 _ _) = "map" tagStr (Form_3 _ _) = "form" tagStr (Label_3 _ _) = "label" tagStr (Input_3 _) = "input" tagStr (Select_3 _ _) = "select" tagStr (Textarea_3 _ _) = "textarea" tagStr (Fieldset_3 _ _) = "fieldset" tagStr (Button_3 _ _) = "button" tagStr (Table_3 _ _) = "table" tagStr (PCDATA_3 _ _) = "PCDATA" instance TagStr Ent4 where tagStr (Script_4 _ _) = "script" tagStr (Ins_4 _ _) = "ins" tagStr (Del_4 _ _) = "del" tagStr (Span_4 _ _) = "span" tagStr (Bdo_4 _ _) = "bdo" tagStr (Br_4 _) = "br" tagStr (Em_4 _ _) = "em" tagStr (Strong_4 _ _) = "strong" tagStr (Dfn_4 _ _) = "dfn" tagStr (Code_4 _ _) = "code" tagStr (Samp_4 _ _) = "samp" tagStr (Kbd_4 _ _) = "kbd" tagStr (Var_4 _ _) = "var" tagStr (Cite_4 _ _) = "cite" tagStr (Abbr_4 _ _) = "abbr" tagStr (Acronym_4 _ _) = "acronym" tagStr (Q_4 _ _) = "q" tagStr (Sub_4 _ _) = "sub" tagStr (Sup_4 _ _) = "sup" tagStr (Tt_4 _ _) = "tt" tagStr (I_4 _ _) = "i" tagStr (B_4 _ _) = "b" tagStr (Big_4 _ _) = "big" tagStr (Small_4 _ _) = "small" tagStr (Object_4 _ _) = "object" tagStr (Img_4 _) = "img" tagStr (Map_4 _ _) = "map" tagStr (Label_4 _ _) = "label" tagStr (Input_4 _) = "input" tagStr (Select_4 _ _) = "select" tagStr (Textarea_4 _ _) = "textarea" tagStr (Button_4 _ _) = "button" tagStr (PCDATA_4 _ _) = "PCDATA" instance TagStr Ent5 where tagStr (Script_5 _ _) = "script" tagStr (Noscript_5 _ _) = "noscript" tagStr (Div_5 _ _) = "div" tagStr (P_5 _ _) = "p" tagStr (H1_5 _ _) = "h1" tagStr (H2_5 _ _) = "h2" tagStr (H3_5 _ _) = "h3" tagStr (H4_5 _ _) = "h4" tagStr (H5_5 _ _) = "h5" tagStr (H6_5 _ _) = "h6" tagStr (Ul_5 _ _) = "ul" tagStr (Ol_5 _ _) = "ol" tagStr (Dl_5 _ _) = "dl" tagStr (Address_5 _ _) = "address" tagStr (Hr_5 _) = "hr" tagStr (Pre_5 _ _) = "pre" tagStr (Blockquote_5 _ _) = "blockquote" tagStr (Ins_5 _ _) = "ins" tagStr (Del_5 _ _) = "del" tagStr (Span_5 _ _) = "span" tagStr (Bdo_5 _ _) = "bdo" tagStr (Br_5 _) = "br" tagStr (Em_5 _ _) = "em" tagStr (Strong_5 _ _) = "strong" tagStr (Dfn_5 _ _) = "dfn" tagStr (Code_5 _ _) = "code" tagStr (Samp_5 _ _) = "samp" tagStr (Kbd_5 _ _) = "kbd" tagStr (Var_5 _ _) = "var" tagStr (Cite_5 _ _) = "cite" tagStr (Abbr_5 _ _) = "abbr" tagStr (Acronym_5 _ _) = "acronym" tagStr (Q_5 _ _) = "q" tagStr (Sub_5 _ _) = "sub" tagStr (Sup_5 _ _) = "sup" tagStr (Tt_5 _ _) = "tt" tagStr (I_5 _ _) = "i" tagStr (B_5 _ _) = "b" tagStr (Big_5 _ _) = "big" tagStr (Small_5 _ _) = "small" tagStr (Object_5 _ _) = "object" tagStr (Img_5 _) = "img" tagStr (Map_5 _ _) = "map" tagStr (Form_5 _ _) = "form" tagStr (Label_5 _ _) = "label" tagStr (Input_5 _) = "input" tagStr (Select_5 _ _) = "select" tagStr (Textarea_5 _ _) = "textarea" tagStr (Fieldset_5 _ _) = "fieldset" tagStr (Button_5 _ _) = "button" tagStr (Table_5 _ _) = "table" tagStr (PCDATA_5 _ _) = "PCDATA" instance TagStr Ent6 where tagStr (Script_6 _ _) = "script" tagStr (Noscript_6 _ _) = "noscript" tagStr (Div_6 _ _) = "div" tagStr (P_6 _ _) = "p" tagStr (H1_6 _ _) = "h1" tagStr (H2_6 _ _) = "h2" tagStr (H3_6 _ _) = "h3" tagStr (H4_6 _ _) = "h4" tagStr (H5_6 _ _) = "h5" tagStr (H6_6 _ _) = "h6" tagStr (Ul_6 _ _) = "ul" tagStr (Ol_6 _ _) = "ol" tagStr (Dl_6 _ _) = "dl" tagStr (Address_6 _ _) = "address" tagStr (Hr_6 _) = "hr" tagStr (Pre_6 _ _) = "pre" tagStr (Blockquote_6 _ _) = "blockquote" tagStr (Ins_6 _ _) = "ins" tagStr (Del_6 _ _) = "del" tagStr (Form_6 _ _) = "form" tagStr (Fieldset_6 _ _) = "fieldset" tagStr (Table_6 _ _) = "table" instance TagStr Ent7 where tagStr (Li_7 _ _) = "li" instance TagStr Ent8 where tagStr (Dt_8 _ _) = "dt" tagStr (Dd_8 _ _) = "dd" instance TagStr Ent9 where tagStr (Script_9 _ _) = "script" tagStr (Ins_9 _ _) = "ins" tagStr (Del_9 _ _) = "del" tagStr (Span_9 _ _) = "span" tagStr (Bdo_9 _ _) = "bdo" tagStr (Br_9 _) = "br" tagStr (Em_9 _ _) = "em" tagStr (Strong_9 _ _) = "strong" tagStr (Dfn_9 _ _) = "dfn" tagStr (Code_9 _ _) = "code" tagStr (Samp_9 _ _) = "samp" tagStr (Kbd_9 _ _) = "kbd" tagStr (Var_9 _ _) = "var" tagStr (Cite_9 _ _) = "cite" tagStr (Abbr_9 _ _) = "abbr" tagStr (Acronym_9 _ _) = "acronym" tagStr (Q_9 _ _) = "q" tagStr (Sub_9 _ _) = "sub" tagStr (Sup_9 _ _) = "sup" tagStr (Tt_9 _ _) = "tt" tagStr (I_9 _ _) = "i" tagStr (B_9 _ _) = "b" tagStr (Big_9 _ _) = "big" tagStr (Small_9 _ _) = "small" tagStr (Map_9 _ _) = "map" tagStr (Label_9 _ _) = "label" tagStr (Input_9 _) = "input" tagStr (Select_9 _ _) = "select" tagStr (Textarea_9 _ _) = "textarea" tagStr (Button_9 _ _) = "button" tagStr (PCDATA_9 _ _) = "PCDATA" instance TagStr Ent10 where tagStr (Script_10 _ _) = "script" tagStr (Noscript_10 _ _) = "noscript" tagStr (Div_10 _ _) = "div" tagStr (P_10 _ _) = "p" tagStr (H1_10 _ _) = "h1" tagStr (H2_10 _ _) = "h2" tagStr (H3_10 _ _) = "h3" tagStr (H4_10 _ _) = "h4" tagStr (H5_10 _ _) = "h5" tagStr (H6_10 _ _) = "h6" tagStr (Ul_10 _ _) = "ul" tagStr (Ol_10 _ _) = "ol" tagStr (Dl_10 _ _) = "dl" tagStr (Address_10 _ _) = "address" tagStr (Hr_10 _) = "hr" tagStr (Pre_10 _ _) = "pre" tagStr (Blockquote_10 _ _) = "blockquote" tagStr (Ins_10 _ _) = "ins" tagStr (Del_10 _ _) = "del" tagStr (Fieldset_10 _ _) = "fieldset" tagStr (Table_10 _ _) = "table" instance TagStr Ent11 where tagStr (Script_11 _ _) = "script" tagStr (Noscript_11 _ _) = "noscript" tagStr (Div_11 _ _) = "div" tagStr (P_11 _ _) = "p" tagStr (H1_11 _ _) = "h1" tagStr (H2_11 _ _) = "h2" tagStr (H3_11 _ _) = "h3" tagStr (H4_11 _ _) = "h4" tagStr (H5_11 _ _) = "h5" tagStr (H6_11 _ _) = "h6" tagStr (Ul_11 _ _) = "ul" tagStr (Ol_11 _ _) = "ol" tagStr (Dl_11 _ _) = "dl" tagStr (Address_11 _ _) = "address" tagStr (Hr_11 _) = "hr" tagStr (Pre_11 _ _) = "pre" tagStr (Blockquote_11 _ _) = "blockquote" tagStr (Ins_11 _ _) = "ins" tagStr (Del_11 _ _) = "del" tagStr (Span_11 _ _) = "span" tagStr (Bdo_11 _ _) = "bdo" tagStr (Br_11 _) = "br" tagStr (Em_11 _ _) = "em" tagStr (Strong_11 _ _) = "strong" tagStr (Dfn_11 _ _) = "dfn" tagStr (Code_11 _ _) = "code" tagStr (Samp_11 _ _) = "samp" tagStr (Kbd_11 _ _) = "kbd" tagStr (Var_11 _ _) = "var" tagStr (Cite_11 _ _) = "cite" tagStr (Abbr_11 _ _) = "abbr" tagStr (Acronym_11 _ _) = "acronym" tagStr (Q_11 _ _) = "q" tagStr (Sub_11 _ _) = "sub" tagStr (Sup_11 _ _) = "sup" tagStr (Tt_11 _ _) = "tt" tagStr (I_11 _ _) = "i" tagStr (B_11 _ _) = "b" tagStr (Big_11 _ _) = "big" tagStr (Small_11 _ _) = "small" tagStr (Object_11 _ _) = "object" tagStr (Img_11 _) = "img" tagStr (Map_11 _ _) = "map" tagStr (Label_11 _ _) = "label" tagStr (Input_11 _) = "input" tagStr (Select_11 _ _) = "select" tagStr (Textarea_11 _ _) = "textarea" tagStr (Fieldset_11 _ _) = "fieldset" tagStr (Button_11 _ _) = "button" tagStr (Table_11 _ _) = "table" tagStr (PCDATA_11 _ _) = "PCDATA" instance TagStr Ent12 where tagStr (Script_12 _ _) = "script" tagStr (Noscript_12 _ _) = "noscript" tagStr (Div_12 _ _) = "div" tagStr (P_12 _ _) = "p" tagStr (H1_12 _ _) = "h1" tagStr (H2_12 _ _) = "h2" tagStr (H3_12 _ _) = "h3" tagStr (H4_12 _ _) = "h4" tagStr (H5_12 _ _) = "h5" tagStr (H6_12 _ _) = "h6" tagStr (Ul_12 _ _) = "ul" tagStr (Ol_12 _ _) = "ol" tagStr (Dl_12 _ _) = "dl" tagStr (Address_12 _ _) = "address" tagStr (Hr_12 _) = "hr" tagStr (Pre_12 _ _) = "pre" tagStr (Blockquote_12 _ _) = "blockquote" tagStr (Ins_12 _ _) = "ins" tagStr (Del_12 _ _) = "del" tagStr (Span_12 _ _) = "span" tagStr (Bdo_12 _ _) = "bdo" tagStr (Br_12 _) = "br" tagStr (Em_12 _ _) = "em" tagStr (Strong_12 _ _) = "strong" tagStr (Dfn_12 _ _) = "dfn" tagStr (Code_12 _ _) = "code" tagStr (Samp_12 _ _) = "samp" tagStr (Kbd_12 _ _) = "kbd" tagStr (Var_12 _ _) = "var" tagStr (Cite_12 _ _) = "cite" tagStr (Abbr_12 _ _) = "abbr" tagStr (Acronym_12 _ _) = "acronym" tagStr (Q_12 _ _) = "q" tagStr (Sub_12 _ _) = "sub" tagStr (Sup_12 _ _) = "sup" tagStr (Tt_12 _ _) = "tt" tagStr (I_12 _ _) = "i" tagStr (B_12 _ _) = "b" tagStr (Big_12 _ _) = "big" tagStr (Small_12 _ _) = "small" tagStr (Object_12 _ _) = "object" tagStr (Img_12 _) = "img" tagStr (Map_12 _ _) = "map" tagStr (Label_12 _ _) = "label" tagStr (Input_12 _) = "input" tagStr (Select_12 _ _) = "select" tagStr (Textarea_12 _ _) = "textarea" tagStr (Fieldset_12 _ _) = "fieldset" tagStr (Legend_12 _ _) = "legend" tagStr (Button_12 _ _) = "button" tagStr (Table_12 _ _) = "table" tagStr (PCDATA_12 _ _) = "PCDATA" instance TagStr Ent13 where tagStr (Caption_13 _ _) = "caption" tagStr (Thead_13 _ _) = "thead" tagStr (Tfoot_13 _ _) = "tfoot" tagStr (Tbody_13 _ _) = "tbody" tagStr (Colgroup_13 _ _) = "colgroup" tagStr (Col_13 _) = "col" tagStr (Tr_13 _ _) = "tr" instance TagStr Ent14 where tagStr (Tr_14 _ _) = "tr" instance TagStr Ent15 where tagStr (Col_15 _) = "col" instance TagStr Ent16 where tagStr (Th_16 _ _) = "th" tagStr (Td_16 _ _) = "td" instance TagStr Ent17 where tagStr (Script_17 _ _) = "script" tagStr (Noscript_17 _ _) = "noscript" tagStr (Div_17 _ _) = "div" tagStr (P_17 _ _) = "p" tagStr (H1_17 _ _) = "h1" tagStr (H2_17 _ _) = "h2" tagStr (H3_17 _ _) = "h3" tagStr (H4_17 _ _) = "h4" tagStr (H5_17 _ _) = "h5" tagStr (H6_17 _ _) = "h6" tagStr (Ul_17 _ _) = "ul" tagStr (Ol_17 _ _) = "ol" tagStr (Dl_17 _ _) = "dl" tagStr (Address_17 _ _) = "address" tagStr (Hr_17 _) = "hr" tagStr (Pre_17 _ _) = "pre" tagStr (Blockquote_17 _ _) = "blockquote" tagStr (Ins_17 _ _) = "ins" tagStr (Del_17 _ _) = "del" tagStr (Span_17 _ _) = "span" tagStr (Bdo_17 _ _) = "bdo" tagStr (Br_17 _) = "br" tagStr (Em_17 _ _) = "em" tagStr (Strong_17 _ _) = "strong" tagStr (Dfn_17 _ _) = "dfn" tagStr (Code_17 _ _) = "code" tagStr (Samp_17 _ _) = "samp" tagStr (Kbd_17 _ _) = "kbd" tagStr (Var_17 _ _) = "var" tagStr (Cite_17 _ _) = "cite" tagStr (Abbr_17 _ _) = "abbr" tagStr (Acronym_17 _ _) = "acronym" tagStr (Q_17 _ _) = "q" tagStr (Sub_17 _ _) = "sub" tagStr (Sup_17 _ _) = "sup" tagStr (Tt_17 _ _) = "tt" tagStr (I_17 _ _) = "i" tagStr (B_17 _ _) = "b" tagStr (Big_17 _ _) = "big" tagStr (Small_17 _ _) = "small" tagStr (Object_17 _ _) = "object" tagStr (Img_17 _) = "img" tagStr (Map_17 _ _) = "map" tagStr (Form_17 _ _) = "form" tagStr (Label_17 _ _) = "label" tagStr (Input_17 _) = "input" tagStr (Select_17 _ _) = "select" tagStr (Textarea_17 _ _) = "textarea" tagStr (Fieldset_17 _ _) = "fieldset" tagStr (Legend_17 _ _) = "legend" tagStr (Button_17 _ _) = "button" tagStr (Table_17 _ _) = "table" tagStr (PCDATA_17 _ _) = "PCDATA" instance TagStr Ent18 where tagStr (Script_18 _ _) = "script" tagStr (Noscript_18 _ _) = "noscript" tagStr (Div_18 _ _) = "div" tagStr (P_18 _ _) = "p" tagStr (H1_18 _ _) = "h1" tagStr (H2_18 _ _) = "h2" tagStr (H3_18 _ _) = "h3" tagStr (H4_18 _ _) = "h4" tagStr (H5_18 _ _) = "h5" tagStr (H6_18 _ _) = "h6" tagStr (Ul_18 _ _) = "ul" tagStr (Ol_18 _ _) = "ol" tagStr (Dl_18 _ _) = "dl" tagStr (Address_18 _ _) = "address" tagStr (Hr_18 _) = "hr" tagStr (Pre_18 _ _) = "pre" tagStr (Blockquote_18 _ _) = "blockquote" tagStr (Ins_18 _ _) = "ins" tagStr (Del_18 _ _) = "del" tagStr (Span_18 _ _) = "span" tagStr (Bdo_18 _ _) = "bdo" tagStr (Br_18 _) = "br" tagStr (Em_18 _ _) = "em" tagStr (Strong_18 _ _) = "strong" tagStr (Dfn_18 _ _) = "dfn" tagStr (Code_18 _ _) = "code" tagStr (Samp_18 _ _) = "samp" tagStr (Kbd_18 _ _) = "kbd" tagStr (Var_18 _ _) = "var" tagStr (Cite_18 _ _) = "cite" tagStr (Abbr_18 _ _) = "abbr" tagStr (Acronym_18 _ _) = "acronym" tagStr (Q_18 _ _) = "q" tagStr (Sub_18 _ _) = "sub" tagStr (Sup_18 _ _) = "sup" tagStr (Tt_18 _ _) = "tt" tagStr (I_18 _ _) = "i" tagStr (B_18 _ _) = "b" tagStr (Big_18 _ _) = "big" tagStr (Small_18 _ _) = "small" tagStr (Object_18 _ _) = "object" tagStr (Param_18 _) = "param" tagStr (Img_18 _) = "img" tagStr (Map_18 _ _) = "map" tagStr (Form_18 _ _) = "form" tagStr (Label_18 _ _) = "label" tagStr (Input_18 _) = "input" tagStr (Select_18 _ _) = "select" tagStr (Textarea_18 _ _) = "textarea" tagStr (Fieldset_18 _ _) = "fieldset" tagStr (Button_18 _ _) = "button" tagStr (Table_18 _ _) = "table" tagStr (PCDATA_18 _ _) = "PCDATA" instance TagStr Ent19 where tagStr (Script_19 _ _) = "script" tagStr (Noscript_19 _ _) = "noscript" tagStr (Div_19 _ _) = "div" tagStr (P_19 _ _) = "p" tagStr (H1_19 _ _) = "h1" tagStr (H2_19 _ _) = "h2" tagStr (H3_19 _ _) = "h3" tagStr (H4_19 _ _) = "h4" tagStr (H5_19 _ _) = "h5" tagStr (H6_19 _ _) = "h6" tagStr (Ul_19 _ _) = "ul" tagStr (Ol_19 _ _) = "ol" tagStr (Dl_19 _ _) = "dl" tagStr (Address_19 _ _) = "address" tagStr (Hr_19 _) = "hr" tagStr (Pre_19 _ _) = "pre" tagStr (Blockquote_19 _ _) = "blockquote" tagStr (Ins_19 _ _) = "ins" tagStr (Del_19 _ _) = "del" tagStr (Area_19 _) = "area" tagStr (Form_19 _ _) = "form" tagStr (Fieldset_19 _ _) = "fieldset" tagStr (Table_19 _ _) = "table" instance TagStr Ent20 where tagStr (Script_20 _ _) = "script" tagStr (Ins_20 _ _) = "ins" tagStr (Del_20 _ _) = "del" tagStr (Span_20 _ _) = "span" tagStr (Bdo_20 _ _) = "bdo" tagStr (Br_20 _) = "br" tagStr (Em_20 _ _) = "em" tagStr (Strong_20 _ _) = "strong" tagStr (Dfn_20 _ _) = "dfn" tagStr (Code_20 _ _) = "code" tagStr (Samp_20 _ _) = "samp" tagStr (Kbd_20 _ _) = "kbd" tagStr (Var_20 _ _) = "var" tagStr (Cite_20 _ _) = "cite" tagStr (Abbr_20 _ _) = "abbr" tagStr (Acronym_20 _ _) = "acronym" tagStr (Q_20 _ _) = "q" tagStr (Sub_20 _ _) = "sub" tagStr (Sup_20 _ _) = "sup" tagStr (Tt_20 _ _) = "tt" tagStr (I_20 _ _) = "i" tagStr (B_20 _ _) = "b" tagStr (Big_20 _ _) = "big" tagStr (Small_20 _ _) = "small" tagStr (Object_20 _ _) = "object" tagStr (Img_20 _) = "img" tagStr (Map_20 _ _) = "map" tagStr (Input_20 _) = "input" tagStr (Select_20 _ _) = "select" tagStr (Textarea_20 _ _) = "textarea" tagStr (Button_20 _ _) = "button" tagStr (PCDATA_20 _ _) = "PCDATA" instance TagStr Ent21 where tagStr (Script_21 _ _) = "script" tagStr (Noscript_21 _ _) = "noscript" tagStr (Div_21 _ _) = "div" tagStr (P_21 _ _) = "p" tagStr (H1_21 _ _) = "h1" tagStr (H2_21 _ _) = "h2" tagStr (H3_21 _ _) = "h3" tagStr (H4_21 _ _) = "h4" tagStr (H5_21 _ _) = "h5" tagStr (H6_21 _ _) = "h6" tagStr (Ul_21 _ _) = "ul" tagStr (Ol_21 _ _) = "ol" tagStr (Dl_21 _ _) = "dl" tagStr (Address_21 _ _) = "address" tagStr (Hr_21 _) = "hr" tagStr (Pre_21 _ _) = "pre" tagStr (Blockquote_21 _ _) = "blockquote" tagStr (Ins_21 _ _) = "ins" tagStr (Del_21 _ _) = "del" tagStr (Span_21 _ _) = "span" tagStr (Bdo_21 _ _) = "bdo" tagStr (Br_21 _) = "br" tagStr (Em_21 _ _) = "em" tagStr (Strong_21 _ _) = "strong" tagStr (Dfn_21 _ _) = "dfn" tagStr (Code_21 _ _) = "code" tagStr (Samp_21 _ _) = "samp" tagStr (Kbd_21 _ _) = "kbd" tagStr (Var_21 _ _) = "var" tagStr (Cite_21 _ _) = "cite" tagStr (Abbr_21 _ _) = "abbr" tagStr (Acronym_21 _ _) = "acronym" tagStr (Q_21 _ _) = "q" tagStr (Sub_21 _ _) = "sub" tagStr (Sup_21 _ _) = "sup" tagStr (Tt_21 _ _) = "tt" tagStr (I_21 _ _) = "i" tagStr (B_21 _ _) = "b" tagStr (Big_21 _ _) = "big" tagStr (Small_21 _ _) = "small" tagStr (Object_21 _ _) = "object" tagStr (Img_21 _) = "img" tagStr (Map_21 _ _) = "map" tagStr (Form_21 _ _) = "form" tagStr (Input_21 _) = "input" tagStr (Select_21 _ _) = "select" tagStr (Textarea_21 _ _) = "textarea" tagStr (Fieldset_21 _ _) = "fieldset" tagStr (Button_21 _ _) = "button" tagStr (Table_21 _ _) = "table" tagStr (PCDATA_21 _ _) = "PCDATA" instance TagStr Ent22 where tagStr (Script_22 _ _) = "script" tagStr (Ins_22 _ _) = "ins" tagStr (Del_22 _ _) = "del" tagStr (Span_22 _ _) = "span" tagStr (Bdo_22 _ _) = "bdo" tagStr (Br_22 _) = "br" tagStr (Em_22 _ _) = "em" tagStr (Strong_22 _ _) = "strong" tagStr (Dfn_22 _ _) = "dfn" tagStr (Code_22 _ _) = "code" tagStr (Samp_22 _ _) = "samp" tagStr (Kbd_22 _ _) = "kbd" tagStr (Var_22 _ _) = "var" tagStr (Cite_22 _ _) = "cite" tagStr (Abbr_22 _ _) = "abbr" tagStr (Acronym_22 _ _) = "acronym" tagStr (Q_22 _ _) = "q" tagStr (Sub_22 _ _) = "sub" tagStr (Sup_22 _ _) = "sup" tagStr (Tt_22 _ _) = "tt" tagStr (I_22 _ _) = "i" tagStr (B_22 _ _) = "b" tagStr (Big_22 _ _) = "big" tagStr (Small_22 _ _) = "small" tagStr (Map_22 _ _) = "map" tagStr (Input_22 _) = "input" tagStr (Select_22 _ _) = "select" tagStr (Textarea_22 _ _) = "textarea" tagStr (Button_22 _ _) = "button" tagStr (PCDATA_22 _ _) = "PCDATA" instance TagStr Ent23 where tagStr (Script_23 _ _) = "script" tagStr (Noscript_23 _ _) = "noscript" tagStr (Div_23 _ _) = "div" tagStr (P_23 _ _) = "p" tagStr (H1_23 _ _) = "h1" tagStr (H2_23 _ _) = "h2" tagStr (H3_23 _ _) = "h3" tagStr (H4_23 _ _) = "h4" tagStr (H5_23 _ _) = "h5" tagStr (H6_23 _ _) = "h6" tagStr (Ul_23 _ _) = "ul" tagStr (Ol_23 _ _) = "ol" tagStr (Dl_23 _ _) = "dl" tagStr (Address_23 _ _) = "address" tagStr (Hr_23 _) = "hr" tagStr (Pre_23 _ _) = "pre" tagStr (Blockquote_23 _ _) = "blockquote" tagStr (Ins_23 _ _) = "ins" tagStr (Del_23 _ _) = "del" tagStr (Span_23 _ _) = "span" tagStr (Bdo_23 _ _) = "bdo" tagStr (Br_23 _) = "br" tagStr (Em_23 _ _) = "em" tagStr (Strong_23 _ _) = "strong" tagStr (Dfn_23 _ _) = "dfn" tagStr (Code_23 _ _) = "code" tagStr (Samp_23 _ _) = "samp" tagStr (Kbd_23 _ _) = "kbd" tagStr (Var_23 _ _) = "var" tagStr (Cite_23 _ _) = "cite" tagStr (Abbr_23 _ _) = "abbr" tagStr (Acronym_23 _ _) = "acronym" tagStr (Q_23 _ _) = "q" tagStr (Sub_23 _ _) = "sub" tagStr (Sup_23 _ _) = "sup" tagStr (Tt_23 _ _) = "tt" tagStr (I_23 _ _) = "i" tagStr (B_23 _ _) = "b" tagStr (Big_23 _ _) = "big" tagStr (Small_23 _ _) = "small" tagStr (Object_23 _ _) = "object" tagStr (Img_23 _) = "img" tagStr (Map_23 _ _) = "map" tagStr (Input_23 _) = "input" tagStr (Select_23 _ _) = "select" tagStr (Textarea_23 _ _) = "textarea" tagStr (Fieldset_23 _ _) = "fieldset" tagStr (Button_23 _ _) = "button" tagStr (Table_23 _ _) = "table" tagStr (PCDATA_23 _ _) = "PCDATA" instance TagStr Ent24 where tagStr (Script_24 _ _) = "script" tagStr (Noscript_24 _ _) = "noscript" tagStr (Div_24 _ _) = "div" tagStr (P_24 _ _) = "p" tagStr (H1_24 _ _) = "h1" tagStr (H2_24 _ _) = "h2" tagStr (H3_24 _ _) = "h3" tagStr (H4_24 _ _) = "h4" tagStr (H5_24 _ _) = "h5" tagStr (H6_24 _ _) = "h6" tagStr (Ul_24 _ _) = "ul" tagStr (Ol_24 _ _) = "ol" tagStr (Dl_24 _ _) = "dl" tagStr (Address_24 _ _) = "address" tagStr (Hr_24 _) = "hr" tagStr (Pre_24 _ _) = "pre" tagStr (Blockquote_24 _ _) = "blockquote" tagStr (Ins_24 _ _) = "ins" tagStr (Del_24 _ _) = "del" tagStr (Span_24 _ _) = "span" tagStr (Bdo_24 _ _) = "bdo" tagStr (Br_24 _) = "br" tagStr (Em_24 _ _) = "em" tagStr (Strong_24 _ _) = "strong" tagStr (Dfn_24 _ _) = "dfn" tagStr (Code_24 _ _) = "code" tagStr (Samp_24 _ _) = "samp" tagStr (Kbd_24 _ _) = "kbd" tagStr (Var_24 _ _) = "var" tagStr (Cite_24 _ _) = "cite" tagStr (Abbr_24 _ _) = "abbr" tagStr (Acronym_24 _ _) = "acronym" tagStr (Q_24 _ _) = "q" tagStr (Sub_24 _ _) = "sub" tagStr (Sup_24 _ _) = "sup" tagStr (Tt_24 _ _) = "tt" tagStr (I_24 _ _) = "i" tagStr (B_24 _ _) = "b" tagStr (Big_24 _ _) = "big" tagStr (Small_24 _ _) = "small" tagStr (Object_24 _ _) = "object" tagStr (Img_24 _) = "img" tagStr (Map_24 _ _) = "map" tagStr (Input_24 _) = "input" tagStr (Select_24 _ _) = "select" tagStr (Textarea_24 _ _) = "textarea" tagStr (Fieldset_24 _ _) = "fieldset" tagStr (Legend_24 _ _) = "legend" tagStr (Button_24 _ _) = "button" tagStr (Table_24 _ _) = "table" tagStr (PCDATA_24 _ _) = "PCDATA" instance TagStr Ent25 where tagStr (Script_25 _ _) = "script" tagStr (Noscript_25 _ _) = "noscript" tagStr (Div_25 _ _) = "div" tagStr (P_25 _ _) = "p" tagStr (H1_25 _ _) = "h1" tagStr (H2_25 _ _) = "h2" tagStr (H3_25 _ _) = "h3" tagStr (H4_25 _ _) = "h4" tagStr (H5_25 _ _) = "h5" tagStr (H6_25 _ _) = "h6" tagStr (Ul_25 _ _) = "ul" tagStr (Ol_25 _ _) = "ol" tagStr (Dl_25 _ _) = "dl" tagStr (Address_25 _ _) = "address" tagStr (Hr_25 _) = "hr" tagStr (Pre_25 _ _) = "pre" tagStr (Blockquote_25 _ _) = "blockquote" tagStr (Ins_25 _ _) = "ins" tagStr (Del_25 _ _) = "del" tagStr (Span_25 _ _) = "span" tagStr (Bdo_25 _ _) = "bdo" tagStr (Br_25 _) = "br" tagStr (Em_25 _ _) = "em" tagStr (Strong_25 _ _) = "strong" tagStr (Dfn_25 _ _) = "dfn" tagStr (Code_25 _ _) = "code" tagStr (Samp_25 _ _) = "samp" tagStr (Kbd_25 _ _) = "kbd" tagStr (Var_25 _ _) = "var" tagStr (Cite_25 _ _) = "cite" tagStr (Abbr_25 _ _) = "abbr" tagStr (Acronym_25 _ _) = "acronym" tagStr (Q_25 _ _) = "q" tagStr (Sub_25 _ _) = "sub" tagStr (Sup_25 _ _) = "sup" tagStr (Tt_25 _ _) = "tt" tagStr (I_25 _ _) = "i" tagStr (B_25 _ _) = "b" tagStr (Big_25 _ _) = "big" tagStr (Small_25 _ _) = "small" tagStr (Object_25 _ _) = "object" tagStr (Img_25 _) = "img" tagStr (Map_25 _ _) = "map" tagStr (Form_25 _ _) = "form" tagStr (Input_25 _) = "input" tagStr (Select_25 _ _) = "select" tagStr (Textarea_25 _ _) = "textarea" tagStr (Fieldset_25 _ _) = "fieldset" tagStr (Legend_25 _ _) = "legend" tagStr (Button_25 _ _) = "button" tagStr (Table_25 _ _) = "table" tagStr (PCDATA_25 _ _) = "PCDATA" instance TagStr Ent26 where tagStr (Script_26 _ _) = "script" tagStr (Noscript_26 _ _) = "noscript" tagStr (Div_26 _ _) = "div" tagStr (P_26 _ _) = "p" tagStr (H1_26 _ _) = "h1" tagStr (H2_26 _ _) = "h2" tagStr (H3_26 _ _) = "h3" tagStr (H4_26 _ _) = "h4" tagStr (H5_26 _ _) = "h5" tagStr (H6_26 _ _) = "h6" tagStr (Ul_26 _ _) = "ul" tagStr (Ol_26 _ _) = "ol" tagStr (Dl_26 _ _) = "dl" tagStr (Address_26 _ _) = "address" tagStr (Hr_26 _) = "hr" tagStr (Pre_26 _ _) = "pre" tagStr (Blockquote_26 _ _) = "blockquote" tagStr (Ins_26 _ _) = "ins" tagStr (Del_26 _ _) = "del" tagStr (Span_26 _ _) = "span" tagStr (Bdo_26 _ _) = "bdo" tagStr (Br_26 _) = "br" tagStr (Em_26 _ _) = "em" tagStr (Strong_26 _ _) = "strong" tagStr (Dfn_26 _ _) = "dfn" tagStr (Code_26 _ _) = "code" tagStr (Samp_26 _ _) = "samp" tagStr (Kbd_26 _ _) = "kbd" tagStr (Var_26 _ _) = "var" tagStr (Cite_26 _ _) = "cite" tagStr (Abbr_26 _ _) = "abbr" tagStr (Acronym_26 _ _) = "acronym" tagStr (Q_26 _ _) = "q" tagStr (Sub_26 _ _) = "sub" tagStr (Sup_26 _ _) = "sup" tagStr (Tt_26 _ _) = "tt" tagStr (I_26 _ _) = "i" tagStr (B_26 _ _) = "b" tagStr (Big_26 _ _) = "big" tagStr (Small_26 _ _) = "small" tagStr (Object_26 _ _) = "object" tagStr (Param_26 _) = "param" tagStr (Img_26 _) = "img" tagStr (Map_26 _ _) = "map" tagStr (Form_26 _ _) = "form" tagStr (Input_26 _) = "input" tagStr (Select_26 _ _) = "select" tagStr (Textarea_26 _ _) = "textarea" tagStr (Fieldset_26 _ _) = "fieldset" tagStr (Button_26 _ _) = "button" tagStr (Table_26 _ _) = "table" tagStr (PCDATA_26 _ _) = "PCDATA" instance TagStr Ent27 where tagStr (Optgroup_27 _ _) = "optgroup" tagStr (Option_27 _ _) = "option" instance TagStr Ent28 where tagStr (Option_28 _ _) = "option" instance TagStr Ent29 where tagStr (Script_29 _ _) = "script" tagStr (Noscript_29 _ _) = "noscript" tagStr (Div_29 _ _) = "div" tagStr (P_29 _ _) = "p" tagStr (H1_29 _ _) = "h1" tagStr (H2_29 _ _) = "h2" tagStr (H3_29 _ _) = "h3" tagStr (H4_29 _ _) = "h4" tagStr (H5_29 _ _) = "h5" tagStr (H6_29 _ _) = "h6" tagStr (Ul_29 _ _) = "ul" tagStr (Ol_29 _ _) = "ol" tagStr (Dl_29 _ _) = "dl" tagStr (Address_29 _ _) = "address" tagStr (Hr_29 _) = "hr" tagStr (Pre_29 _ _) = "pre" tagStr (Blockquote_29 _ _) = "blockquote" tagStr (Ins_29 _ _) = "ins" tagStr (Del_29 _ _) = "del" tagStr (Span_29 _ _) = "span" tagStr (Bdo_29 _ _) = "bdo" tagStr (Br_29 _) = "br" tagStr (Em_29 _ _) = "em" tagStr (Strong_29 _ _) = "strong" tagStr (Dfn_29 _ _) = "dfn" tagStr (Code_29 _ _) = "code" tagStr (Samp_29 _ _) = "samp" tagStr (Kbd_29 _ _) = "kbd" tagStr (Var_29 _ _) = "var" tagStr (Cite_29 _ _) = "cite" tagStr (Abbr_29 _ _) = "abbr" tagStr (Acronym_29 _ _) = "acronym" tagStr (Q_29 _ _) = "q" tagStr (Sub_29 _ _) = "sub" tagStr (Sup_29 _ _) = "sup" tagStr (Tt_29 _ _) = "tt" tagStr (I_29 _ _) = "i" tagStr (B_29 _ _) = "b" tagStr (Big_29 _ _) = "big" tagStr (Small_29 _ _) = "small" tagStr (Object_29 _ _) = "object" tagStr (Img_29 _) = "img" tagStr (Map_29 _ _) = "map" tagStr (Table_29 _ _) = "table" tagStr (PCDATA_29 _ _) = "PCDATA" instance TagStr Ent30 where tagStr (Script_30 _ _) = "script" tagStr (Ins_30 _ _) = "ins" tagStr (Del_30 _ _) = "del" tagStr (A_30 _ _) = "a" tagStr (Span_30 _ _) = "span" tagStr (Bdo_30 _ _) = "bdo" tagStr (Br_30 _) = "br" tagStr (Em_30 _ _) = "em" tagStr (Strong_30 _ _) = "strong" tagStr (Dfn_30 _ _) = "dfn" tagStr (Code_30 _ _) = "code" tagStr (Samp_30 _ _) = "samp" tagStr (Kbd_30 _ _) = "kbd" tagStr (Var_30 _ _) = "var" tagStr (Cite_30 _ _) = "cite" tagStr (Abbr_30 _ _) = "abbr" tagStr (Acronym_30 _ _) = "acronym" tagStr (Q_30 _ _) = "q" tagStr (Sub_30 _ _) = "sub" tagStr (Sup_30 _ _) = "sup" tagStr (Tt_30 _ _) = "tt" tagStr (I_30 _ _) = "i" tagStr (B_30 _ _) = "b" tagStr (Big_30 _ _) = "big" tagStr (Small_30 _ _) = "small" tagStr (Object_30 _ _) = "object" tagStr (Img_30 _) = "img" tagStr (Map_30 _ _) = "map" tagStr (Label_30 _ _) = "label" tagStr (Input_30 _) = "input" tagStr (Select_30 _ _) = "select" tagStr (Textarea_30 _ _) = "textarea" tagStr (Button_30 _ _) = "button" tagStr (PCDATA_30 _ _) = "PCDATA" instance TagStr Ent31 where tagStr (Script_31 _ _) = "script" tagStr (Ins_31 _ _) = "ins" tagStr (Del_31 _ _) = "del" tagStr (A_31 _ _) = "a" tagStr (Span_31 _ _) = "span" tagStr (Bdo_31 _ _) = "bdo" tagStr (Br_31 _) = "br" tagStr (Em_31 _ _) = "em" tagStr (Strong_31 _ _) = "strong" tagStr (Dfn_31 _ _) = "dfn" tagStr (Code_31 _ _) = "code" tagStr (Samp_31 _ _) = "samp" tagStr (Kbd_31 _ _) = "kbd" tagStr (Var_31 _ _) = "var" tagStr (Cite_31 _ _) = "cite" tagStr (Abbr_31 _ _) = "abbr" tagStr (Acronym_31 _ _) = "acronym" tagStr (Q_31 _ _) = "q" tagStr (Sub_31 _ _) = "sub" tagStr (Sup_31 _ _) = "sup" tagStr (Tt_31 _ _) = "tt" tagStr (I_31 _ _) = "i" tagStr (B_31 _ _) = "b" tagStr (Big_31 _ _) = "big" tagStr (Small_31 _ _) = "small" tagStr (Object_31 _ _) = "object" tagStr (Img_31 _) = "img" tagStr (Map_31 _ _) = "map" tagStr (Input_31 _) = "input" tagStr (Select_31 _ _) = "select" tagStr (Textarea_31 _ _) = "textarea" tagStr (Button_31 _ _) = "button" tagStr (PCDATA_31 _ _) = "PCDATA" instance TagStr Ent32 where tagStr (Script_32 _ _) = "script" tagStr (Noscript_32 _ _) = "noscript" tagStr (Div_32 _ _) = "div" tagStr (P_32 _ _) = "p" tagStr (H1_32 _ _) = "h1" tagStr (H2_32 _ _) = "h2" tagStr (H3_32 _ _) = "h3" tagStr (H4_32 _ _) = "h4" tagStr (H5_32 _ _) = "h5" tagStr (H6_32 _ _) = "h6" tagStr (Ul_32 _ _) = "ul" tagStr (Ol_32 _ _) = "ol" tagStr (Dl_32 _ _) = "dl" tagStr (Address_32 _ _) = "address" tagStr (Hr_32 _) = "hr" tagStr (Pre_32 _ _) = "pre" tagStr (Blockquote_32 _ _) = "blockquote" tagStr (Ins_32 _ _) = "ins" tagStr (Del_32 _ _) = "del" tagStr (A_32 _ _) = "a" tagStr (Span_32 _ _) = "span" tagStr (Bdo_32 _ _) = "bdo" tagStr (Br_32 _) = "br" tagStr (Em_32 _ _) = "em" tagStr (Strong_32 _ _) = "strong" tagStr (Dfn_32 _ _) = "dfn" tagStr (Code_32 _ _) = "code" tagStr (Samp_32 _ _) = "samp" tagStr (Kbd_32 _ _) = "kbd" tagStr (Var_32 _ _) = "var" tagStr (Cite_32 _ _) = "cite" tagStr (Abbr_32 _ _) = "abbr" tagStr (Acronym_32 _ _) = "acronym" tagStr (Q_32 _ _) = "q" tagStr (Sub_32 _ _) = "sub" tagStr (Sup_32 _ _) = "sup" tagStr (Tt_32 _ _) = "tt" tagStr (I_32 _ _) = "i" tagStr (B_32 _ _) = "b" tagStr (Big_32 _ _) = "big" tagStr (Small_32 _ _) = "small" tagStr (Object_32 _ _) = "object" tagStr (Img_32 _) = "img" tagStr (Map_32 _ _) = "map" tagStr (Form_32 _ _) = "form" tagStr (Input_32 _) = "input" tagStr (Select_32 _ _) = "select" tagStr (Textarea_32 _ _) = "textarea" tagStr (Fieldset_32 _ _) = "fieldset" tagStr (Button_32 _ _) = "button" tagStr (Table_32 _ _) = "table" tagStr (PCDATA_32 _ _) = "PCDATA" instance TagStr Ent33 where tagStr (Script_33 _ _) = "script" tagStr (Ins_33 _ _) = "ins" tagStr (Del_33 _ _) = "del" tagStr (A_33 _ _) = "a" tagStr (Span_33 _ _) = "span" tagStr (Bdo_33 _ _) = "bdo" tagStr (Br_33 _) = "br" tagStr (Em_33 _ _) = "em" tagStr (Strong_33 _ _) = "strong" tagStr (Dfn_33 _ _) = "dfn" tagStr (Code_33 _ _) = "code" tagStr (Samp_33 _ _) = "samp" tagStr (Kbd_33 _ _) = "kbd" tagStr (Var_33 _ _) = "var" tagStr (Cite_33 _ _) = "cite" tagStr (Abbr_33 _ _) = "abbr" tagStr (Acronym_33 _ _) = "acronym" tagStr (Q_33 _ _) = "q" tagStr (Sub_33 _ _) = "sub" tagStr (Sup_33 _ _) = "sup" tagStr (Tt_33 _ _) = "tt" tagStr (I_33 _ _) = "i" tagStr (B_33 _ _) = "b" tagStr (Big_33 _ _) = "big" tagStr (Small_33 _ _) = "small" tagStr (Map_33 _ _) = "map" tagStr (Input_33 _) = "input" tagStr (Select_33 _ _) = "select" tagStr (Textarea_33 _ _) = "textarea" tagStr (Button_33 _ _) = "button" tagStr (PCDATA_33 _ _) = "PCDATA" instance TagStr Ent34 where tagStr (Script_34 _ _) = "script" tagStr (Noscript_34 _ _) = "noscript" tagStr (Div_34 _ _) = "div" tagStr (P_34 _ _) = "p" tagStr (H1_34 _ _) = "h1" tagStr (H2_34 _ _) = "h2" tagStr (H3_34 _ _) = "h3" tagStr (H4_34 _ _) = "h4" tagStr (H5_34 _ _) = "h5" tagStr (H6_34 _ _) = "h6" tagStr (Ul_34 _ _) = "ul" tagStr (Ol_34 _ _) = "ol" tagStr (Dl_34 _ _) = "dl" tagStr (Address_34 _ _) = "address" tagStr (Hr_34 _) = "hr" tagStr (Pre_34 _ _) = "pre" tagStr (Blockquote_34 _ _) = "blockquote" tagStr (Ins_34 _ _) = "ins" tagStr (Del_34 _ _) = "del" tagStr (A_34 _ _) = "a" tagStr (Span_34 _ _) = "span" tagStr (Bdo_34 _ _) = "bdo" tagStr (Br_34 _) = "br" tagStr (Em_34 _ _) = "em" tagStr (Strong_34 _ _) = "strong" tagStr (Dfn_34 _ _) = "dfn" tagStr (Code_34 _ _) = "code" tagStr (Samp_34 _ _) = "samp" tagStr (Kbd_34 _ _) = "kbd" tagStr (Var_34 _ _) = "var" tagStr (Cite_34 _ _) = "cite" tagStr (Abbr_34 _ _) = "abbr" tagStr (Acronym_34 _ _) = "acronym" tagStr (Q_34 _ _) = "q" tagStr (Sub_34 _ _) = "sub" tagStr (Sup_34 _ _) = "sup" tagStr (Tt_34 _ _) = "tt" tagStr (I_34 _ _) = "i" tagStr (B_34 _ _) = "b" tagStr (Big_34 _ _) = "big" tagStr (Small_34 _ _) = "small" tagStr (Object_34 _ _) = "object" tagStr (Img_34 _) = "img" tagStr (Map_34 _ _) = "map" tagStr (Input_34 _) = "input" tagStr (Select_34 _ _) = "select" tagStr (Textarea_34 _ _) = "textarea" tagStr (Fieldset_34 _ _) = "fieldset" tagStr (Button_34 _ _) = "button" tagStr (Table_34 _ _) = "table" tagStr (PCDATA_34 _ _) = "PCDATA" instance TagStr Ent35 where tagStr (Script_35 _ _) = "script" tagStr (Noscript_35 _ _) = "noscript" tagStr (Div_35 _ _) = "div" tagStr (P_35 _ _) = "p" tagStr (H1_35 _ _) = "h1" tagStr (H2_35 _ _) = "h2" tagStr (H3_35 _ _) = "h3" tagStr (H4_35 _ _) = "h4" tagStr (H5_35 _ _) = "h5" tagStr (H6_35 _ _) = "h6" tagStr (Ul_35 _ _) = "ul" tagStr (Ol_35 _ _) = "ol" tagStr (Dl_35 _ _) = "dl" tagStr (Address_35 _ _) = "address" tagStr (Hr_35 _) = "hr" tagStr (Pre_35 _ _) = "pre" tagStr (Blockquote_35 _ _) = "blockquote" tagStr (Ins_35 _ _) = "ins" tagStr (Del_35 _ _) = "del" tagStr (A_35 _ _) = "a" tagStr (Span_35 _ _) = "span" tagStr (Bdo_35 _ _) = "bdo" tagStr (Br_35 _) = "br" tagStr (Em_35 _ _) = "em" tagStr (Strong_35 _ _) = "strong" tagStr (Dfn_35 _ _) = "dfn" tagStr (Code_35 _ _) = "code" tagStr (Samp_35 _ _) = "samp" tagStr (Kbd_35 _ _) = "kbd" tagStr (Var_35 _ _) = "var" tagStr (Cite_35 _ _) = "cite" tagStr (Abbr_35 _ _) = "abbr" tagStr (Acronym_35 _ _) = "acronym" tagStr (Q_35 _ _) = "q" tagStr (Sub_35 _ _) = "sub" tagStr (Sup_35 _ _) = "sup" tagStr (Tt_35 _ _) = "tt" tagStr (I_35 _ _) = "i" tagStr (B_35 _ _) = "b" tagStr (Big_35 _ _) = "big" tagStr (Small_35 _ _) = "small" tagStr (Object_35 _ _) = "object" tagStr (Img_35 _) = "img" tagStr (Map_35 _ _) = "map" tagStr (Input_35 _) = "input" tagStr (Select_35 _ _) = "select" tagStr (Textarea_35 _ _) = "textarea" tagStr (Fieldset_35 _ _) = "fieldset" tagStr (Legend_35 _ _) = "legend" tagStr (Button_35 _ _) = "button" tagStr (Table_35 _ _) = "table" tagStr (PCDATA_35 _ _) = "PCDATA" instance TagStr Ent36 where tagStr (Script_36 _ _) = "script" tagStr (Noscript_36 _ _) = "noscript" tagStr (Div_36 _ _) = "div" tagStr (P_36 _ _) = "p" tagStr (H1_36 _ _) = "h1" tagStr (H2_36 _ _) = "h2" tagStr (H3_36 _ _) = "h3" tagStr (H4_36 _ _) = "h4" tagStr (H5_36 _ _) = "h5" tagStr (H6_36 _ _) = "h6" tagStr (Ul_36 _ _) = "ul" tagStr (Ol_36 _ _) = "ol" tagStr (Dl_36 _ _) = "dl" tagStr (Address_36 _ _) = "address" tagStr (Hr_36 _) = "hr" tagStr (Pre_36 _ _) = "pre" tagStr (Blockquote_36 _ _) = "blockquote" tagStr (Ins_36 _ _) = "ins" tagStr (Del_36 _ _) = "del" tagStr (A_36 _ _) = "a" tagStr (Span_36 _ _) = "span" tagStr (Bdo_36 _ _) = "bdo" tagStr (Br_36 _) = "br" tagStr (Em_36 _ _) = "em" tagStr (Strong_36 _ _) = "strong" tagStr (Dfn_36 _ _) = "dfn" tagStr (Code_36 _ _) = "code" tagStr (Samp_36 _ _) = "samp" tagStr (Kbd_36 _ _) = "kbd" tagStr (Var_36 _ _) = "var" tagStr (Cite_36 _ _) = "cite" tagStr (Abbr_36 _ _) = "abbr" tagStr (Acronym_36 _ _) = "acronym" tagStr (Q_36 _ _) = "q" tagStr (Sub_36 _ _) = "sub" tagStr (Sup_36 _ _) = "sup" tagStr (Tt_36 _ _) = "tt" tagStr (I_36 _ _) = "i" tagStr (B_36 _ _) = "b" tagStr (Big_36 _ _) = "big" tagStr (Small_36 _ _) = "small" tagStr (Object_36 _ _) = "object" tagStr (Img_36 _) = "img" tagStr (Map_36 _ _) = "map" tagStr (Form_36 _ _) = "form" tagStr (Input_36 _) = "input" tagStr (Select_36 _ _) = "select" tagStr (Textarea_36 _ _) = "textarea" tagStr (Fieldset_36 _ _) = "fieldset" tagStr (Legend_36 _ _) = "legend" tagStr (Button_36 _ _) = "button" tagStr (Table_36 _ _) = "table" tagStr (PCDATA_36 _ _) = "PCDATA" instance TagStr Ent37 where tagStr (Script_37 _ _) = "script" tagStr (Noscript_37 _ _) = "noscript" tagStr (Div_37 _ _) = "div" tagStr (P_37 _ _) = "p" tagStr (H1_37 _ _) = "h1" tagStr (H2_37 _ _) = "h2" tagStr (H3_37 _ _) = "h3" tagStr (H4_37 _ _) = "h4" tagStr (H5_37 _ _) = "h5" tagStr (H6_37 _ _) = "h6" tagStr (Ul_37 _ _) = "ul" tagStr (Ol_37 _ _) = "ol" tagStr (Dl_37 _ _) = "dl" tagStr (Address_37 _ _) = "address" tagStr (Hr_37 _) = "hr" tagStr (Pre_37 _ _) = "pre" tagStr (Blockquote_37 _ _) = "blockquote" tagStr (Ins_37 _ _) = "ins" tagStr (Del_37 _ _) = "del" tagStr (A_37 _ _) = "a" tagStr (Span_37 _ _) = "span" tagStr (Bdo_37 _ _) = "bdo" tagStr (Br_37 _) = "br" tagStr (Em_37 _ _) = "em" tagStr (Strong_37 _ _) = "strong" tagStr (Dfn_37 _ _) = "dfn" tagStr (Code_37 _ _) = "code" tagStr (Samp_37 _ _) = "samp" tagStr (Kbd_37 _ _) = "kbd" tagStr (Var_37 _ _) = "var" tagStr (Cite_37 _ _) = "cite" tagStr (Abbr_37 _ _) = "abbr" tagStr (Acronym_37 _ _) = "acronym" tagStr (Q_37 _ _) = "q" tagStr (Sub_37 _ _) = "sub" tagStr (Sup_37 _ _) = "sup" tagStr (Tt_37 _ _) = "tt" tagStr (I_37 _ _) = "i" tagStr (B_37 _ _) = "b" tagStr (Big_37 _ _) = "big" tagStr (Small_37 _ _) = "small" tagStr (Object_37 _ _) = "object" tagStr (Param_37 _) = "param" tagStr (Img_37 _) = "img" tagStr (Map_37 _ _) = "map" tagStr (Form_37 _ _) = "form" tagStr (Input_37 _) = "input" tagStr (Select_37 _ _) = "select" tagStr (Textarea_37 _ _) = "textarea" tagStr (Fieldset_37 _ _) = "fieldset" tagStr (Button_37 _ _) = "button" tagStr (Table_37 _ _) = "table" tagStr (PCDATA_37 _ _) = "PCDATA" instance TagStr Ent38 where tagStr (Script_38 _ _) = "script" tagStr (Noscript_38 _ _) = "noscript" tagStr (Div_38 _ _) = "div" tagStr (P_38 _ _) = "p" tagStr (H1_38 _ _) = "h1" tagStr (H2_38 _ _) = "h2" tagStr (H3_38 _ _) = "h3" tagStr (H4_38 _ _) = "h4" tagStr (H5_38 _ _) = "h5" tagStr (H6_38 _ _) = "h6" tagStr (Ul_38 _ _) = "ul" tagStr (Ol_38 _ _) = "ol" tagStr (Dl_38 _ _) = "dl" tagStr (Address_38 _ _) = "address" tagStr (Hr_38 _) = "hr" tagStr (Pre_38 _ _) = "pre" tagStr (Blockquote_38 _ _) = "blockquote" tagStr (Ins_38 _ _) = "ins" tagStr (Del_38 _ _) = "del" tagStr (A_38 _ _) = "a" tagStr (Span_38 _ _) = "span" tagStr (Bdo_38 _ _) = "bdo" tagStr (Br_38 _) = "br" tagStr (Em_38 _ _) = "em" tagStr (Strong_38 _ _) = "strong" tagStr (Dfn_38 _ _) = "dfn" tagStr (Code_38 _ _) = "code" tagStr (Samp_38 _ _) = "samp" tagStr (Kbd_38 _ _) = "kbd" tagStr (Var_38 _ _) = "var" tagStr (Cite_38 _ _) = "cite" tagStr (Abbr_38 _ _) = "abbr" tagStr (Acronym_38 _ _) = "acronym" tagStr (Q_38 _ _) = "q" tagStr (Sub_38 _ _) = "sub" tagStr (Sup_38 _ _) = "sup" tagStr (Tt_38 _ _) = "tt" tagStr (I_38 _ _) = "i" tagStr (B_38 _ _) = "b" tagStr (Big_38 _ _) = "big" tagStr (Small_38 _ _) = "small" tagStr (Object_38 _ _) = "object" tagStr (Img_38 _) = "img" tagStr (Map_38 _ _) = "map" tagStr (Form_38 _ _) = "form" tagStr (Label_38 _ _) = "label" tagStr (Input_38 _) = "input" tagStr (Select_38 _ _) = "select" tagStr (Textarea_38 _ _) = "textarea" tagStr (Fieldset_38 _ _) = "fieldset" tagStr (Button_38 _ _) = "button" tagStr (Table_38 _ _) = "table" tagStr (PCDATA_38 _ _) = "PCDATA" instance TagStr Ent39 where tagStr (Script_39 _ _) = "script" tagStr (Ins_39 _ _) = "ins" tagStr (Del_39 _ _) = "del" tagStr (A_39 _ _) = "a" tagStr (Span_39 _ _) = "span" tagStr (Bdo_39 _ _) = "bdo" tagStr (Br_39 _) = "br" tagStr (Em_39 _ _) = "em" tagStr (Strong_39 _ _) = "strong" tagStr (Dfn_39 _ _) = "dfn" tagStr (Code_39 _ _) = "code" tagStr (Samp_39 _ _) = "samp" tagStr (Kbd_39 _ _) = "kbd" tagStr (Var_39 _ _) = "var" tagStr (Cite_39 _ _) = "cite" tagStr (Abbr_39 _ _) = "abbr" tagStr (Acronym_39 _ _) = "acronym" tagStr (Q_39 _ _) = "q" tagStr (Sub_39 _ _) = "sub" tagStr (Sup_39 _ _) = "sup" tagStr (Tt_39 _ _) = "tt" tagStr (I_39 _ _) = "i" tagStr (B_39 _ _) = "b" tagStr (Big_39 _ _) = "big" tagStr (Small_39 _ _) = "small" tagStr (Map_39 _ _) = "map" tagStr (Label_39 _ _) = "label" tagStr (Input_39 _) = "input" tagStr (Select_39 _ _) = "select" tagStr (Textarea_39 _ _) = "textarea" tagStr (Button_39 _ _) = "button" tagStr (PCDATA_39 _ _) = "PCDATA" instance TagStr Ent40 where tagStr (Script_40 _ _) = "script" tagStr (Noscript_40 _ _) = "noscript" tagStr (Div_40 _ _) = "div" tagStr (P_40 _ _) = "p" tagStr (H1_40 _ _) = "h1" tagStr (H2_40 _ _) = "h2" tagStr (H3_40 _ _) = "h3" tagStr (H4_40 _ _) = "h4" tagStr (H5_40 _ _) = "h5" tagStr (H6_40 _ _) = "h6" tagStr (Ul_40 _ _) = "ul" tagStr (Ol_40 _ _) = "ol" tagStr (Dl_40 _ _) = "dl" tagStr (Address_40 _ _) = "address" tagStr (Hr_40 _) = "hr" tagStr (Pre_40 _ _) = "pre" tagStr (Blockquote_40 _ _) = "blockquote" tagStr (Ins_40 _ _) = "ins" tagStr (Del_40 _ _) = "del" tagStr (A_40 _ _) = "a" tagStr (Span_40 _ _) = "span" tagStr (Bdo_40 _ _) = "bdo" tagStr (Br_40 _) = "br" tagStr (Em_40 _ _) = "em" tagStr (Strong_40 _ _) = "strong" tagStr (Dfn_40 _ _) = "dfn" tagStr (Code_40 _ _) = "code" tagStr (Samp_40 _ _) = "samp" tagStr (Kbd_40 _ _) = "kbd" tagStr (Var_40 _ _) = "var" tagStr (Cite_40 _ _) = "cite" tagStr (Abbr_40 _ _) = "abbr" tagStr (Acronym_40 _ _) = "acronym" tagStr (Q_40 _ _) = "q" tagStr (Sub_40 _ _) = "sub" tagStr (Sup_40 _ _) = "sup" tagStr (Tt_40 _ _) = "tt" tagStr (I_40 _ _) = "i" tagStr (B_40 _ _) = "b" tagStr (Big_40 _ _) = "big" tagStr (Small_40 _ _) = "small" tagStr (Object_40 _ _) = "object" tagStr (Img_40 _) = "img" tagStr (Map_40 _ _) = "map" tagStr (Label_40 _ _) = "label" tagStr (Input_40 _) = "input" tagStr (Select_40 _ _) = "select" tagStr (Textarea_40 _ _) = "textarea" tagStr (Fieldset_40 _ _) = "fieldset" tagStr (Button_40 _ _) = "button" tagStr (Table_40 _ _) = "table" tagStr (PCDATA_40 _ _) = "PCDATA" instance TagStr Ent41 where tagStr (Script_41 _ _) = "script" tagStr (Noscript_41 _ _) = "noscript" tagStr (Div_41 _ _) = "div" tagStr (P_41 _ _) = "p" tagStr (H1_41 _ _) = "h1" tagStr (H2_41 _ _) = "h2" tagStr (H3_41 _ _) = "h3" tagStr (H4_41 _ _) = "h4" tagStr (H5_41 _ _) = "h5" tagStr (H6_41 _ _) = "h6" tagStr (Ul_41 _ _) = "ul" tagStr (Ol_41 _ _) = "ol" tagStr (Dl_41 _ _) = "dl" tagStr (Address_41 _ _) = "address" tagStr (Hr_41 _) = "hr" tagStr (Pre_41 _ _) = "pre" tagStr (Blockquote_41 _ _) = "blockquote" tagStr (Ins_41 _ _) = "ins" tagStr (Del_41 _ _) = "del" tagStr (Span_41 _ _) = "span" tagStr (Bdo_41 _ _) = "bdo" tagStr (Br_41 _) = "br" tagStr (Em_41 _ _) = "em" tagStr (Strong_41 _ _) = "strong" tagStr (Dfn_41 _ _) = "dfn" tagStr (Code_41 _ _) = "code" tagStr (Samp_41 _ _) = "samp" tagStr (Kbd_41 _ _) = "kbd" tagStr (Var_41 _ _) = "var" tagStr (Cite_41 _ _) = "cite" tagStr (Abbr_41 _ _) = "abbr" tagStr (Acronym_41 _ _) = "acronym" tagStr (Q_41 _ _) = "q" tagStr (Sub_41 _ _) = "sub" tagStr (Sup_41 _ _) = "sup" tagStr (Tt_41 _ _) = "tt" tagStr (I_41 _ _) = "i" tagStr (B_41 _ _) = "b" tagStr (Big_41 _ _) = "big" tagStr (Small_41 _ _) = "small" tagStr (Object_41 _ _) = "object" tagStr (Param_41 _) = "param" tagStr (Img_41 _) = "img" tagStr (Map_41 _ _) = "map" tagStr (Label_41 _ _) = "label" tagStr (Input_41 _) = "input" tagStr (Select_41 _ _) = "select" tagStr (Textarea_41 _ _) = "textarea" tagStr (Fieldset_41 _ _) = "fieldset" tagStr (Button_41 _ _) = "button" tagStr (Table_41 _ _) = "table" tagStr (PCDATA_41 _ _) = "PCDATA" instance TagStr Ent42 where tagStr (Script_42 _ _) = "script" tagStr (Noscript_42 _ _) = "noscript" tagStr (Div_42 _ _) = "div" tagStr (P_42 _ _) = "p" tagStr (H1_42 _ _) = "h1" tagStr (H2_42 _ _) = "h2" tagStr (H3_42 _ _) = "h3" tagStr (H4_42 _ _) = "h4" tagStr (H5_42 _ _) = "h5" tagStr (H6_42 _ _) = "h6" tagStr (Ul_42 _ _) = "ul" tagStr (Ol_42 _ _) = "ol" tagStr (Dl_42 _ _) = "dl" tagStr (Address_42 _ _) = "address" tagStr (Hr_42 _) = "hr" tagStr (Pre_42 _ _) = "pre" tagStr (Blockquote_42 _ _) = "blockquote" tagStr (Ins_42 _ _) = "ins" tagStr (Del_42 _ _) = "del" tagStr (Area_42 _) = "area" tagStr (Fieldset_42 _ _) = "fieldset" tagStr (Table_42 _ _) = "table" instance TagStr Ent43 where tagStr (Script_43 _ _) = "script" tagStr (Noscript_43 _ _) = "noscript" tagStr (Div_43 _ _) = "div" tagStr (P_43 _ _) = "p" tagStr (H1_43 _ _) = "h1" tagStr (H2_43 _ _) = "h2" tagStr (H3_43 _ _) = "h3" tagStr (H4_43 _ _) = "h4" tagStr (H5_43 _ _) = "h5" tagStr (H6_43 _ _) = "h6" tagStr (Ul_43 _ _) = "ul" tagStr (Ol_43 _ _) = "ol" tagStr (Dl_43 _ _) = "dl" tagStr (Address_43 _ _) = "address" tagStr (Hr_43 _) = "hr" tagStr (Pre_43 _ _) = "pre" tagStr (Blockquote_43 _ _) = "blockquote" tagStr (Ins_43 _ _) = "ins" tagStr (Del_43 _ _) = "del" tagStr (Span_43 _ _) = "span" tagStr (Bdo_43 _ _) = "bdo" tagStr (Br_43 _) = "br" tagStr (Em_43 _ _) = "em" tagStr (Strong_43 _ _) = "strong" tagStr (Dfn_43 _ _) = "dfn" tagStr (Code_43 _ _) = "code" tagStr (Samp_43 _ _) = "samp" tagStr (Kbd_43 _ _) = "kbd" tagStr (Var_43 _ _) = "var" tagStr (Cite_43 _ _) = "cite" tagStr (Abbr_43 _ _) = "abbr" tagStr (Acronym_43 _ _) = "acronym" tagStr (Q_43 _ _) = "q" tagStr (Sub_43 _ _) = "sub" tagStr (Sup_43 _ _) = "sup" tagStr (Tt_43 _ _) = "tt" tagStr (I_43 _ _) = "i" tagStr (B_43 _ _) = "b" tagStr (Big_43 _ _) = "big" tagStr (Small_43 _ _) = "small" tagStr (Object_43 _ _) = "object" tagStr (Param_43 _) = "param" tagStr (Img_43 _) = "img" tagStr (Map_43 _ _) = "map" tagStr (Input_43 _) = "input" tagStr (Select_43 _ _) = "select" tagStr (Textarea_43 _ _) = "textarea" tagStr (Fieldset_43 _ _) = "fieldset" tagStr (Button_43 _ _) = "button" tagStr (Table_43 _ _) = "table" tagStr (PCDATA_43 _ _) = "PCDATA" instance TagStr Ent44 where tagStr (Script_44 _ _) = "script" tagStr (Noscript_44 _ _) = "noscript" tagStr (Div_44 _ _) = "div" tagStr (P_44 _ _) = "p" tagStr (H1_44 _ _) = "h1" tagStr (H2_44 _ _) = "h2" tagStr (H3_44 _ _) = "h3" tagStr (H4_44 _ _) = "h4" tagStr (H5_44 _ _) = "h5" tagStr (H6_44 _ _) = "h6" tagStr (Ul_44 _ _) = "ul" tagStr (Ol_44 _ _) = "ol" tagStr (Dl_44 _ _) = "dl" tagStr (Address_44 _ _) = "address" tagStr (Hr_44 _) = "hr" tagStr (Pre_44 _ _) = "pre" tagStr (Blockquote_44 _ _) = "blockquote" tagStr (Ins_44 _ _) = "ins" tagStr (Del_44 _ _) = "del" tagStr (A_44 _ _) = "a" tagStr (Span_44 _ _) = "span" tagStr (Bdo_44 _ _) = "bdo" tagStr (Br_44 _) = "br" tagStr (Em_44 _ _) = "em" tagStr (Strong_44 _ _) = "strong" tagStr (Dfn_44 _ _) = "dfn" tagStr (Code_44 _ _) = "code" tagStr (Samp_44 _ _) = "samp" tagStr (Kbd_44 _ _) = "kbd" tagStr (Var_44 _ _) = "var" tagStr (Cite_44 _ _) = "cite" tagStr (Abbr_44 _ _) = "abbr" tagStr (Acronym_44 _ _) = "acronym" tagStr (Q_44 _ _) = "q" tagStr (Sub_44 _ _) = "sub" tagStr (Sup_44 _ _) = "sup" tagStr (Tt_44 _ _) = "tt" tagStr (I_44 _ _) = "i" tagStr (B_44 _ _) = "b" tagStr (Big_44 _ _) = "big" tagStr (Small_44 _ _) = "small" tagStr (Object_44 _ _) = "object" tagStr (Param_44 _) = "param" tagStr (Img_44 _) = "img" tagStr (Map_44 _ _) = "map" tagStr (Label_44 _ _) = "label" tagStr (Input_44 _) = "input" tagStr (Select_44 _ _) = "select" tagStr (Textarea_44 _ _) = "textarea" tagStr (Fieldset_44 _ _) = "fieldset" tagStr (Button_44 _ _) = "button" tagStr (Table_44 _ _) = "table" tagStr (PCDATA_44 _ _) = "PCDATA" instance TagStr Ent45 where tagStr (Script_45 _ _) = "script" tagStr (Noscript_45 _ _) = "noscript" tagStr (Div_45 _ _) = "div" tagStr (P_45 _ _) = "p" tagStr (H1_45 _ _) = "h1" tagStr (H2_45 _ _) = "h2" tagStr (H3_45 _ _) = "h3" tagStr (H4_45 _ _) = "h4" tagStr (H5_45 _ _) = "h5" tagStr (H6_45 _ _) = "h6" tagStr (Ul_45 _ _) = "ul" tagStr (Ol_45 _ _) = "ol" tagStr (Dl_45 _ _) = "dl" tagStr (Address_45 _ _) = "address" tagStr (Hr_45 _) = "hr" tagStr (Pre_45 _ _) = "pre" tagStr (Blockquote_45 _ _) = "blockquote" tagStr (Ins_45 _ _) = "ins" tagStr (Del_45 _ _) = "del" tagStr (A_45 _ _) = "a" tagStr (Span_45 _ _) = "span" tagStr (Bdo_45 _ _) = "bdo" tagStr (Br_45 _) = "br" tagStr (Em_45 _ _) = "em" tagStr (Strong_45 _ _) = "strong" tagStr (Dfn_45 _ _) = "dfn" tagStr (Code_45 _ _) = "code" tagStr (Samp_45 _ _) = "samp" tagStr (Kbd_45 _ _) = "kbd" tagStr (Var_45 _ _) = "var" tagStr (Cite_45 _ _) = "cite" tagStr (Abbr_45 _ _) = "abbr" tagStr (Acronym_45 _ _) = "acronym" tagStr (Q_45 _ _) = "q" tagStr (Sub_45 _ _) = "sub" tagStr (Sup_45 _ _) = "sup" tagStr (Tt_45 _ _) = "tt" tagStr (I_45 _ _) = "i" tagStr (B_45 _ _) = "b" tagStr (Big_45 _ _) = "big" tagStr (Small_45 _ _) = "small" tagStr (Object_45 _ _) = "object" tagStr (Param_45 _) = "param" tagStr (Img_45 _) = "img" tagStr (Map_45 _ _) = "map" tagStr (Input_45 _) = "input" tagStr (Select_45 _ _) = "select" tagStr (Textarea_45 _ _) = "textarea" tagStr (Fieldset_45 _ _) = "fieldset" tagStr (Button_45 _ _) = "button" tagStr (Table_45 _ _) = "table" tagStr (PCDATA_45 _ _) = "PCDATA" instance TagStr Ent46 where tagStr (Script_46 _ _) = "script" tagStr (Noscript_46 _ _) = "noscript" tagStr (Div_46 _ _) = "div" tagStr (P_46 _ _) = "p" tagStr (H1_46 _ _) = "h1" tagStr (H2_46 _ _) = "h2" tagStr (H3_46 _ _) = "h3" tagStr (H4_46 _ _) = "h4" tagStr (H5_46 _ _) = "h5" tagStr (H6_46 _ _) = "h6" tagStr (Ul_46 _ _) = "ul" tagStr (Ol_46 _ _) = "ol" tagStr (Dl_46 _ _) = "dl" tagStr (Address_46 _ _) = "address" tagStr (Hr_46 _) = "hr" tagStr (Pre_46 _ _) = "pre" tagStr (Blockquote_46 _ _) = "blockquote" tagStr (Ins_46 _ _) = "ins" tagStr (Del_46 _ _) = "del" tagStr (A_46 _ _) = "a" tagStr (Span_46 _ _) = "span" tagStr (Bdo_46 _ _) = "bdo" tagStr (Br_46 _) = "br" tagStr (Em_46 _ _) = "em" tagStr (Strong_46 _ _) = "strong" tagStr (Dfn_46 _ _) = "dfn" tagStr (Code_46 _ _) = "code" tagStr (Samp_46 _ _) = "samp" tagStr (Kbd_46 _ _) = "kbd" tagStr (Var_46 _ _) = "var" tagStr (Cite_46 _ _) = "cite" tagStr (Abbr_46 _ _) = "abbr" tagStr (Acronym_46 _ _) = "acronym" tagStr (Q_46 _ _) = "q" tagStr (Sub_46 _ _) = "sub" tagStr (Sup_46 _ _) = "sup" tagStr (Tt_46 _ _) = "tt" tagStr (I_46 _ _) = "i" tagStr (B_46 _ _) = "b" tagStr (Big_46 _ _) = "big" tagStr (Small_46 _ _) = "small" tagStr (Object_46 _ _) = "object" tagStr (Img_46 _) = "img" tagStr (Map_46 _ _) = "map" tagStr (Label_46 _ _) = "label" tagStr (Input_46 _) = "input" tagStr (Select_46 _ _) = "select" tagStr (Textarea_46 _ _) = "textarea" tagStr (Fieldset_46 _ _) = "fieldset" tagStr (Legend_46 _ _) = "legend" tagStr (Button_46 _ _) = "button" tagStr (Table_46 _ _) = "table" tagStr (PCDATA_46 _ _) = "PCDATA" instance TagStr Ent47 where tagStr (Script_47 _ _) = "script" tagStr (Noscript_47 _ _) = "noscript" tagStr (Div_47 _ _) = "div" tagStr (P_47 _ _) = "p" tagStr (H1_47 _ _) = "h1" tagStr (H2_47 _ _) = "h2" tagStr (H3_47 _ _) = "h3" tagStr (H4_47 _ _) = "h4" tagStr (H5_47 _ _) = "h5" tagStr (H6_47 _ _) = "h6" tagStr (Ul_47 _ _) = "ul" tagStr (Ol_47 _ _) = "ol" tagStr (Dl_47 _ _) = "dl" tagStr (Address_47 _ _) = "address" tagStr (Hr_47 _) = "hr" tagStr (Pre_47 _ _) = "pre" tagStr (Blockquote_47 _ _) = "blockquote" tagStr (Ins_47 _ _) = "ins" tagStr (Del_47 _ _) = "del" tagStr (A_47 _ _) = "a" tagStr (Span_47 _ _) = "span" tagStr (Bdo_47 _ _) = "bdo" tagStr (Br_47 _) = "br" tagStr (Em_47 _ _) = "em" tagStr (Strong_47 _ _) = "strong" tagStr (Dfn_47 _ _) = "dfn" tagStr (Code_47 _ _) = "code" tagStr (Samp_47 _ _) = "samp" tagStr (Kbd_47 _ _) = "kbd" tagStr (Var_47 _ _) = "var" tagStr (Cite_47 _ _) = "cite" tagStr (Abbr_47 _ _) = "abbr" tagStr (Acronym_47 _ _) = "acronym" tagStr (Q_47 _ _) = "q" tagStr (Sub_47 _ _) = "sub" tagStr (Sup_47 _ _) = "sup" tagStr (Tt_47 _ _) = "tt" tagStr (I_47 _ _) = "i" tagStr (B_47 _ _) = "b" tagStr (Big_47 _ _) = "big" tagStr (Small_47 _ _) = "small" tagStr (Object_47 _ _) = "object" tagStr (Img_47 _) = "img" tagStr (Map_47 _ _) = "map" tagStr (Form_47 _ _) = "form" tagStr (Label_47 _ _) = "label" tagStr (Input_47 _) = "input" tagStr (Select_47 _ _) = "select" tagStr (Textarea_47 _ _) = "textarea" tagStr (Fieldset_47 _ _) = "fieldset" tagStr (Legend_47 _ _) = "legend" tagStr (Button_47 _ _) = "button" tagStr (Table_47 _ _) = "table" tagStr (PCDATA_47 _ _) = "PCDATA" class TagChildren a where tagChildren :: a -> [(String,[String])] instance TagChildren Ent where tagChildren (Html att c) = ("html",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent0 where tagChildren (Head_0 _ c) = ("head",map tagStr c):(concatMap tagChildren c) tagChildren (Body_0 _ c) = ("body",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent1 where tagChildren (Title_1 _ c) = ("title",map tagStr c):(concatMap tagChildren c) tagChildren (Base_1 _) = [] tagChildren (Meta_1 _) = [] tagChildren (Link_1 _) = [] tagChildren (Style_1 _ c) = ("style",map tagStr c):(concatMap tagChildren c) tagChildren (Script_1 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Object_1 _ c) = ("object",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent2 where tagChildren (PCDATA_2 _ _) = [] instance TagChildren Ent3 where tagChildren (Script_3 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_3 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_3 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_3 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_3 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_3 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_3 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_3 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_3 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_3 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_3 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_3 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_3 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_3 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_3 _) = [] tagChildren (Pre_3 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_3 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_3 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_3 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_3 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_3 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_3 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_3 _) = [] tagChildren (Em_3 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_3 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_3 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_3 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_3 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_3 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_3 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_3 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_3 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_3 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_3 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_3 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_3 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_3 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_3 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_3 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_3 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_3 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_3 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_3 _) = [] tagChildren (Img_3 _) = [] tagChildren (Map_3 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_3 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_3 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_3 _) = [] tagChildren (Select_3 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_3 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_3 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_3 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_3 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_3 _ _) = [] instance TagChildren Ent4 where tagChildren (Script_4 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_4 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_4 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_4 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_4 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_4 _) = [] tagChildren (Em_4 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_4 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_4 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_4 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_4 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_4 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_4 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_4 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_4 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_4 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_4 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_4 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_4 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_4 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_4 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_4 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_4 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_4 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_4 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_4 _) = [] tagChildren (Map_4 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_4 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_4 _) = [] tagChildren (Select_4 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_4 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_4 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_4 _ _) = [] instance TagChildren Ent5 where tagChildren (Script_5 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_5 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_5 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_5 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_5 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_5 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_5 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_5 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_5 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_5 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_5 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_5 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_5 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_5 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_5 _) = [] tagChildren (Pre_5 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_5 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_5 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_5 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_5 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_5 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_5 _) = [] tagChildren (Em_5 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_5 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_5 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_5 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_5 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_5 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_5 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_5 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_5 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_5 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_5 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_5 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_5 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_5 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_5 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_5 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_5 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_5 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_5 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_5 _) = [] tagChildren (Map_5 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_5 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_5 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_5 _) = [] tagChildren (Select_5 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_5 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_5 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_5 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_5 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_5 _ _) = [] instance TagChildren Ent6 where tagChildren (Script_6 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_6 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_6 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_6 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_6 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_6 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_6 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_6 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_6 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_6 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_6 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_6 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_6 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_6 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_6 _) = [] tagChildren (Pre_6 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_6 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_6 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_6 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Form_6 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_6 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Table_6 _ c) = ("table",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent7 where tagChildren (Li_7 _ c) = ("li",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent8 where tagChildren (Dt_8 _ c) = ("dt",map tagStr c):(concatMap tagChildren c) tagChildren (Dd_8 _ c) = ("dd",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent9 where tagChildren (Script_9 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_9 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_9 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_9 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_9 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_9 _) = [] tagChildren (Em_9 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_9 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_9 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_9 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_9 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_9 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_9 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_9 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_9 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_9 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_9 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_9 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_9 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_9 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_9 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_9 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_9 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_9 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Map_9 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_9 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_9 _) = [] tagChildren (Select_9 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_9 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_9 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_9 _ _) = [] instance TagChildren Ent10 where tagChildren (Script_10 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_10 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_10 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_10 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_10 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_10 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_10 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_10 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_10 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_10 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_10 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_10 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_10 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_10 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_10 _) = [] tagChildren (Pre_10 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_10 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_10 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_10 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_10 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Table_10 _ c) = ("table",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent11 where tagChildren (Script_11 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_11 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_11 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_11 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_11 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_11 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_11 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_11 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_11 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_11 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_11 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_11 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_11 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_11 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_11 _) = [] tagChildren (Pre_11 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_11 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_11 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_11 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_11 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_11 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_11 _) = [] tagChildren (Em_11 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_11 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_11 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_11 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_11 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_11 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_11 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_11 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_11 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_11 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_11 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_11 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_11 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_11 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_11 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_11 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_11 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_11 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_11 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_11 _) = [] tagChildren (Map_11 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_11 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_11 _) = [] tagChildren (Select_11 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_11 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_11 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_11 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_11 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_11 _ _) = [] instance TagChildren Ent12 where tagChildren (Script_12 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_12 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_12 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_12 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_12 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_12 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_12 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_12 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_12 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_12 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_12 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_12 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_12 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_12 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_12 _) = [] tagChildren (Pre_12 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_12 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_12 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_12 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_12 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_12 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_12 _) = [] tagChildren (Em_12 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_12 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_12 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_12 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_12 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_12 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_12 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_12 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_12 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_12 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_12 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_12 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_12 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_12 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_12 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_12 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_12 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_12 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_12 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_12 _) = [] tagChildren (Map_12 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_12 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_12 _) = [] tagChildren (Select_12 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_12 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_12 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_12 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_12 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_12 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_12 _ _) = [] instance TagChildren Ent13 where tagChildren (Caption_13 _ c) = ("caption",map tagStr c):(concatMap tagChildren c) tagChildren (Thead_13 _ c) = ("thead",map tagStr c):(concatMap tagChildren c) tagChildren (Tfoot_13 _ c) = ("tfoot",map tagStr c):(concatMap tagChildren c) tagChildren (Tbody_13 _ c) = ("tbody",map tagStr c):(concatMap tagChildren c) tagChildren (Colgroup_13 _ c) = ("colgroup",map tagStr c):(concatMap tagChildren c) tagChildren (Col_13 _) = [] tagChildren (Tr_13 _ c) = ("tr",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent14 where tagChildren (Tr_14 _ c) = ("tr",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent15 where tagChildren (Col_15 _) = [] instance TagChildren Ent16 where tagChildren (Th_16 _ c) = ("th",map tagStr c):(concatMap tagChildren c) tagChildren (Td_16 _ c) = ("td",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent17 where tagChildren (Script_17 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_17 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_17 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_17 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_17 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_17 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_17 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_17 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_17 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_17 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_17 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_17 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_17 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_17 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_17 _) = [] tagChildren (Pre_17 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_17 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_17 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_17 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_17 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_17 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_17 _) = [] tagChildren (Em_17 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_17 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_17 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_17 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_17 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_17 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_17 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_17 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_17 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_17 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_17 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_17 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_17 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_17 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_17 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_17 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_17 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_17 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_17 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_17 _) = [] tagChildren (Map_17 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_17 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_17 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_17 _) = [] tagChildren (Select_17 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_17 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_17 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_17 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_17 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_17 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_17 _ _) = [] instance TagChildren Ent18 where tagChildren (Script_18 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_18 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_18 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_18 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_18 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_18 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_18 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_18 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_18 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_18 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_18 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_18 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_18 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_18 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_18 _) = [] tagChildren (Pre_18 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_18 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_18 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_18 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_18 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_18 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_18 _) = [] tagChildren (Em_18 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_18 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_18 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_18 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_18 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_18 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_18 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_18 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_18 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_18 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_18 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_18 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_18 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_18 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_18 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_18 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_18 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_18 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_18 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_18 _) = [] tagChildren (Img_18 _) = [] tagChildren (Map_18 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_18 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_18 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_18 _) = [] tagChildren (Select_18 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_18 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_18 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_18 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_18 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_18 _ _) = [] instance TagChildren Ent19 where tagChildren (Script_19 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_19 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_19 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_19 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_19 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_19 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_19 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_19 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_19 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_19 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_19 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_19 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_19 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_19 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_19 _) = [] tagChildren (Pre_19 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_19 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_19 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_19 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Area_19 _) = [] tagChildren (Form_19 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_19 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Table_19 _ c) = ("table",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent20 where tagChildren (Script_20 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_20 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_20 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_20 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_20 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_20 _) = [] tagChildren (Em_20 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_20 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_20 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_20 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_20 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_20 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_20 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_20 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_20 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_20 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_20 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_20 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_20 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_20 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_20 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_20 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_20 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_20 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_20 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_20 _) = [] tagChildren (Map_20 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_20 _) = [] tagChildren (Select_20 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_20 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_20 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_20 _ _) = [] instance TagChildren Ent21 where tagChildren (Script_21 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_21 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_21 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_21 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_21 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_21 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_21 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_21 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_21 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_21 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_21 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_21 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_21 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_21 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_21 _) = [] tagChildren (Pre_21 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_21 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_21 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_21 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_21 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_21 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_21 _) = [] tagChildren (Em_21 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_21 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_21 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_21 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_21 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_21 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_21 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_21 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_21 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_21 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_21 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_21 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_21 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_21 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_21 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_21 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_21 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_21 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_21 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_21 _) = [] tagChildren (Map_21 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_21 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_21 _) = [] tagChildren (Select_21 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_21 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_21 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_21 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_21 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_21 _ _) = [] instance TagChildren Ent22 where tagChildren (Script_22 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_22 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_22 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_22 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_22 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_22 _) = [] tagChildren (Em_22 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_22 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_22 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_22 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_22 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_22 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_22 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_22 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_22 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_22 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_22 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_22 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_22 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_22 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_22 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_22 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_22 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_22 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Map_22 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_22 _) = [] tagChildren (Select_22 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_22 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_22 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_22 _ _) = [] instance TagChildren Ent23 where tagChildren (Script_23 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_23 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_23 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_23 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_23 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_23 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_23 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_23 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_23 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_23 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_23 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_23 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_23 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_23 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_23 _) = [] tagChildren (Pre_23 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_23 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_23 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_23 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_23 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_23 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_23 _) = [] tagChildren (Em_23 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_23 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_23 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_23 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_23 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_23 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_23 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_23 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_23 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_23 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_23 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_23 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_23 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_23 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_23 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_23 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_23 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_23 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_23 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_23 _) = [] tagChildren (Map_23 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_23 _) = [] tagChildren (Select_23 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_23 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_23 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_23 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_23 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_23 _ _) = [] instance TagChildren Ent24 where tagChildren (Script_24 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_24 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_24 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_24 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_24 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_24 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_24 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_24 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_24 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_24 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_24 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_24 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_24 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_24 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_24 _) = [] tagChildren (Pre_24 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_24 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_24 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_24 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_24 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_24 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_24 _) = [] tagChildren (Em_24 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_24 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_24 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_24 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_24 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_24 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_24 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_24 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_24 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_24 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_24 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_24 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_24 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_24 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_24 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_24 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_24 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_24 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_24 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_24 _) = [] tagChildren (Map_24 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_24 _) = [] tagChildren (Select_24 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_24 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_24 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_24 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_24 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_24 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_24 _ _) = [] instance TagChildren Ent25 where tagChildren (Script_25 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_25 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_25 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_25 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_25 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_25 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_25 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_25 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_25 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_25 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_25 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_25 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_25 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_25 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_25 _) = [] tagChildren (Pre_25 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_25 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_25 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_25 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_25 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_25 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_25 _) = [] tagChildren (Em_25 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_25 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_25 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_25 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_25 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_25 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_25 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_25 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_25 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_25 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_25 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_25 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_25 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_25 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_25 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_25 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_25 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_25 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_25 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_25 _) = [] tagChildren (Map_25 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_25 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_25 _) = [] tagChildren (Select_25 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_25 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_25 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_25 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_25 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_25 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_25 _ _) = [] instance TagChildren Ent26 where tagChildren (Script_26 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_26 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_26 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_26 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_26 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_26 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_26 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_26 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_26 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_26 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_26 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_26 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_26 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_26 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_26 _) = [] tagChildren (Pre_26 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_26 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_26 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_26 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_26 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_26 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_26 _) = [] tagChildren (Em_26 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_26 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_26 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_26 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_26 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_26 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_26 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_26 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_26 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_26 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_26 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_26 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_26 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_26 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_26 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_26 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_26 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_26 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_26 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_26 _) = [] tagChildren (Img_26 _) = [] tagChildren (Map_26 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_26 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_26 _) = [] tagChildren (Select_26 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_26 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_26 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_26 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_26 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_26 _ _) = [] instance TagChildren Ent27 where tagChildren (Optgroup_27 _ c) = ("optgroup",map tagStr c):(concatMap tagChildren c) tagChildren (Option_27 _ c) = ("option",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent28 where tagChildren (Option_28 _ c) = ("option",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent29 where tagChildren (Script_29 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_29 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_29 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_29 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_29 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_29 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_29 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_29 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_29 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_29 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_29 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_29 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_29 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_29 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_29 _) = [] tagChildren (Pre_29 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_29 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_29 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_29 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_29 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_29 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_29 _) = [] tagChildren (Em_29 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_29 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_29 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_29 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_29 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_29 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_29 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_29 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_29 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_29 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_29 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_29 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_29 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_29 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_29 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_29 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_29 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_29 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_29 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_29 _) = [] tagChildren (Map_29 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Table_29 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_29 _ _) = [] instance TagChildren Ent30 where tagChildren (Script_30 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_30 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_30 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_30 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_30 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_30 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_30 _) = [] tagChildren (Em_30 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_30 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_30 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_30 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_30 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_30 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_30 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_30 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_30 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_30 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_30 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_30 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_30 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_30 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_30 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_30 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_30 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_30 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_30 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_30 _) = [] tagChildren (Map_30 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_30 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_30 _) = [] tagChildren (Select_30 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_30 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_30 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_30 _ _) = [] instance TagChildren Ent31 where tagChildren (Script_31 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_31 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_31 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_31 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_31 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_31 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_31 _) = [] tagChildren (Em_31 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_31 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_31 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_31 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_31 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_31 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_31 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_31 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_31 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_31 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_31 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_31 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_31 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_31 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_31 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_31 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_31 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_31 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_31 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_31 _) = [] tagChildren (Map_31 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_31 _) = [] tagChildren (Select_31 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_31 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_31 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_31 _ _) = [] instance TagChildren Ent32 where tagChildren (Script_32 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_32 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_32 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_32 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_32 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_32 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_32 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_32 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_32 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_32 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_32 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_32 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_32 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_32 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_32 _) = [] tagChildren (Pre_32 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_32 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_32 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_32 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_32 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_32 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_32 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_32 _) = [] tagChildren (Em_32 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_32 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_32 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_32 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_32 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_32 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_32 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_32 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_32 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_32 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_32 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_32 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_32 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_32 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_32 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_32 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_32 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_32 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_32 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_32 _) = [] tagChildren (Map_32 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_32 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_32 _) = [] tagChildren (Select_32 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_32 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_32 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_32 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_32 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_32 _ _) = [] instance TagChildren Ent33 where tagChildren (Script_33 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_33 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_33 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_33 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_33 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_33 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_33 _) = [] tagChildren (Em_33 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_33 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_33 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_33 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_33 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_33 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_33 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_33 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_33 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_33 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_33 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_33 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_33 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_33 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_33 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_33 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_33 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_33 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Map_33 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_33 _) = [] tagChildren (Select_33 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_33 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_33 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_33 _ _) = [] instance TagChildren Ent34 where tagChildren (Script_34 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_34 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_34 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_34 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_34 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_34 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_34 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_34 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_34 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_34 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_34 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_34 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_34 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_34 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_34 _) = [] tagChildren (Pre_34 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_34 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_34 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_34 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_34 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_34 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_34 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_34 _) = [] tagChildren (Em_34 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_34 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_34 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_34 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_34 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_34 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_34 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_34 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_34 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_34 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_34 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_34 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_34 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_34 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_34 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_34 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_34 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_34 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_34 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_34 _) = [] tagChildren (Map_34 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_34 _) = [] tagChildren (Select_34 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_34 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_34 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_34 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_34 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_34 _ _) = [] instance TagChildren Ent35 where tagChildren (Script_35 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_35 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_35 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_35 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_35 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_35 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_35 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_35 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_35 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_35 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_35 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_35 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_35 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_35 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_35 _) = [] tagChildren (Pre_35 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_35 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_35 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_35 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_35 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_35 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_35 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_35 _) = [] tagChildren (Em_35 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_35 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_35 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_35 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_35 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_35 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_35 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_35 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_35 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_35 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_35 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_35 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_35 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_35 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_35 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_35 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_35 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_35 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_35 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_35 _) = [] tagChildren (Map_35 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_35 _) = [] tagChildren (Select_35 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_35 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_35 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_35 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_35 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_35 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_35 _ _) = [] instance TagChildren Ent36 where tagChildren (Script_36 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_36 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_36 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_36 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_36 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_36 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_36 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_36 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_36 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_36 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_36 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_36 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_36 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_36 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_36 _) = [] tagChildren (Pre_36 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_36 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_36 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_36 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_36 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_36 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_36 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_36 _) = [] tagChildren (Em_36 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_36 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_36 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_36 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_36 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_36 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_36 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_36 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_36 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_36 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_36 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_36 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_36 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_36 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_36 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_36 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_36 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_36 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_36 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_36 _) = [] tagChildren (Map_36 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_36 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_36 _) = [] tagChildren (Select_36 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_36 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_36 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_36 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_36 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_36 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_36 _ _) = [] instance TagChildren Ent37 where tagChildren (Script_37 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_37 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_37 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_37 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_37 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_37 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_37 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_37 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_37 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_37 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_37 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_37 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_37 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_37 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_37 _) = [] tagChildren (Pre_37 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_37 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_37 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_37 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_37 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_37 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_37 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_37 _) = [] tagChildren (Em_37 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_37 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_37 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_37 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_37 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_37 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_37 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_37 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_37 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_37 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_37 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_37 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_37 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_37 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_37 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_37 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_37 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_37 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_37 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_37 _) = [] tagChildren (Img_37 _) = [] tagChildren (Map_37 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_37 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_37 _) = [] tagChildren (Select_37 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_37 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_37 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_37 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_37 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_37 _ _) = [] instance TagChildren Ent38 where tagChildren (Script_38 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_38 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_38 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_38 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_38 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_38 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_38 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_38 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_38 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_38 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_38 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_38 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_38 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_38 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_38 _) = [] tagChildren (Pre_38 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_38 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_38 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_38 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_38 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_38 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_38 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_38 _) = [] tagChildren (Em_38 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_38 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_38 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_38 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_38 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_38 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_38 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_38 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_38 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_38 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_38 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_38 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_38 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_38 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_38 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_38 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_38 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_38 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_38 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_38 _) = [] tagChildren (Map_38 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_38 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_38 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_38 _) = [] tagChildren (Select_38 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_38 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_38 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_38 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_38 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_38 _ _) = [] instance TagChildren Ent39 where tagChildren (Script_39 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_39 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_39 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_39 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_39 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_39 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_39 _) = [] tagChildren (Em_39 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_39 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_39 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_39 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_39 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_39 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_39 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_39 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_39 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_39 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_39 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_39 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_39 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_39 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_39 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_39 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_39 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_39 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Map_39 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_39 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_39 _) = [] tagChildren (Select_39 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_39 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_39 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_39 _ _) = [] instance TagChildren Ent40 where tagChildren (Script_40 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_40 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_40 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_40 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_40 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_40 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_40 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_40 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_40 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_40 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_40 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_40 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_40 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_40 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_40 _) = [] tagChildren (Pre_40 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_40 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_40 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_40 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_40 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_40 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_40 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_40 _) = [] tagChildren (Em_40 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_40 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_40 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_40 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_40 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_40 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_40 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_40 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_40 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_40 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_40 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_40 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_40 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_40 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_40 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_40 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_40 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_40 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_40 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_40 _) = [] tagChildren (Map_40 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_40 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_40 _) = [] tagChildren (Select_40 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_40 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_40 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_40 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_40 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_40 _ _) = [] instance TagChildren Ent41 where tagChildren (Script_41 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_41 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_41 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_41 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_41 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_41 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_41 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_41 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_41 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_41 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_41 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_41 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_41 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_41 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_41 _) = [] tagChildren (Pre_41 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_41 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_41 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_41 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_41 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_41 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_41 _) = [] tagChildren (Em_41 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_41 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_41 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_41 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_41 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_41 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_41 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_41 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_41 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_41 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_41 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_41 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_41 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_41 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_41 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_41 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_41 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_41 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_41 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_41 _) = [] tagChildren (Img_41 _) = [] tagChildren (Map_41 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_41 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_41 _) = [] tagChildren (Select_41 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_41 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_41 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_41 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_41 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_41 _ _) = [] instance TagChildren Ent42 where tagChildren (Script_42 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_42 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_42 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_42 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_42 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_42 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_42 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_42 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_42 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_42 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_42 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_42 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_42 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_42 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_42 _) = [] tagChildren (Pre_42 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_42 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_42 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_42 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Area_42 _) = [] tagChildren (Fieldset_42 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Table_42 _ c) = ("table",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent43 where tagChildren (Script_43 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_43 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_43 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_43 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_43 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_43 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_43 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_43 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_43 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_43 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_43 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_43 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_43 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_43 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_43 _) = [] tagChildren (Pre_43 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_43 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_43 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_43 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_43 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_43 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_43 _) = [] tagChildren (Em_43 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_43 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_43 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_43 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_43 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_43 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_43 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_43 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_43 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_43 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_43 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_43 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_43 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_43 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_43 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_43 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_43 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_43 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_43 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_43 _) = [] tagChildren (Img_43 _) = [] tagChildren (Map_43 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_43 _) = [] tagChildren (Select_43 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_43 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_43 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_43 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_43 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_43 _ _) = [] instance TagChildren Ent44 where tagChildren (Script_44 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_44 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_44 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_44 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_44 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_44 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_44 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_44 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_44 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_44 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_44 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_44 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_44 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_44 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_44 _) = [] tagChildren (Pre_44 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_44 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_44 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_44 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_44 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_44 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_44 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_44 _) = [] tagChildren (Em_44 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_44 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_44 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_44 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_44 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_44 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_44 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_44 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_44 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_44 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_44 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_44 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_44 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_44 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_44 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_44 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_44 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_44 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_44 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_44 _) = [] tagChildren (Img_44 _) = [] tagChildren (Map_44 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_44 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_44 _) = [] tagChildren (Select_44 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_44 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_44 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_44 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_44 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_44 _ _) = [] instance TagChildren Ent45 where tagChildren (Script_45 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_45 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_45 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_45 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_45 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_45 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_45 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_45 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_45 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_45 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_45 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_45 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_45 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_45 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_45 _) = [] tagChildren (Pre_45 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_45 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_45 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_45 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_45 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_45 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_45 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_45 _) = [] tagChildren (Em_45 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_45 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_45 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_45 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_45 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_45 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_45 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_45 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_45 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_45 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_45 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_45 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_45 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_45 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_45 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_45 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_45 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_45 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_45 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_45 _) = [] tagChildren (Img_45 _) = [] tagChildren (Map_45 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_45 _) = [] tagChildren (Select_45 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_45 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_45 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_45 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_45 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_45 _ _) = [] instance TagChildren Ent46 where tagChildren (Script_46 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_46 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_46 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_46 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_46 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_46 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_46 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_46 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_46 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_46 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_46 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_46 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_46 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_46 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_46 _) = [] tagChildren (Pre_46 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_46 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_46 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_46 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_46 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_46 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_46 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_46 _) = [] tagChildren (Em_46 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_46 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_46 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_46 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_46 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_46 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_46 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_46 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_46 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_46 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_46 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_46 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_46 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_46 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_46 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_46 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_46 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_46 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_46 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_46 _) = [] tagChildren (Map_46 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_46 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_46 _) = [] tagChildren (Select_46 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_46 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_46 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_46 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_46 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_46 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_46 _ _) = [] instance TagChildren Ent47 where tagChildren (Script_47 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_47 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_47 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_47 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_47 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_47 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_47 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_47 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_47 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_47 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_47 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_47 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_47 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_47 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_47 _) = [] tagChildren (Pre_47 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_47 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_47 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_47 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_47 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_47 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_47 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_47 _) = [] tagChildren (Em_47 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_47 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_47 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_47 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_47 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_47 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_47 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_47 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_47 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_47 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_47 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_47 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_47 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_47 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_47 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_47 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_47 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_47 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (Object_47 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Img_47 _) = [] tagChildren (Map_47 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_47 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_47 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_47 _) = [] tagChildren (Select_47 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_47 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_47 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_47 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_47 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Table_47 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_47 _ _) = [] allowchildren = [("html","^((head)(body))$","(head,body)"),("head","^(((script)|(style)|(meta)|(link)|(object))*(((title)((script)|(style)|(meta)|(link)|(object))*((base)((script)|(style)|(meta)|(link)|(object))*)?)|((base)((script)|(style)|(meta)|(link)|(object))*((title)((script)|(style)|(meta)|(link)|(object))*))))$","((script|style|meta|link|object)*,((title,(script|style|meta|link|object)*,(base,(script|style|meta|link|object)*)?)|(base,(script|style|meta|link|object)*,(title,(script|style|meta|link|object)*))))"),("title","^(PCDATA)$","(#PCDATA)"),("base","^EMPTY$","EMPTY"),("meta","^EMPTY$","EMPTY"),("link","^EMPTY$","EMPTY"),("style","^(PCDATA)$","(#PCDATA)"),("script","^(PCDATA)$","(#PCDATA)"),("noscript","^((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))*$","(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)*"),("body","^((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))*$","(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)*"),("div","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("p","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h1","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h2","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h3","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h4","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h5","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h6","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("ul","^((li))+$","(li)+"),("ol","^((li))+$","(li)+"),("li","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("dl","^((dt)|(dd))+$","(dt|dd)+"),("dt","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("dd","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("address","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("hr","^EMPTY$","EMPTY"),("pre","^(PCDATA|(a)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(br)|(span)|(bdo)|(map)|(ins)|(del)|(script)|(input)|(select)|(textarea)|(label)|(button))*$","(#PCDATA|a|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|br|span|bdo|map|ins|del|script|input|select|textarea|label|button)*"),("blockquote","^((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))*$","(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)*"),("ins","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("del","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("a","^(PCDATA|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("span","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("bdo","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("br","^EMPTY$","EMPTY"),("em","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("strong","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("dfn","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("code","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("samp","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("kbd","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("var","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("cite","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("abbr","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("acronym","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("q","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("sub","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("sup","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("tt","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("i","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("b","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("big","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("small","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("object","^(PCDATA|(param)|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|param|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("param","^EMPTY$","EMPTY"),("img","^EMPTY$","EMPTY"),("map","^(((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))+|(area)+)$","((p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)+|area+)"),("area","^EMPTY$","EMPTY"),("form","^((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(noscript)|(ins)|(del)|(script))*$","(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|noscript|ins|del|script)*"),("label","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("input","^EMPTY$","EMPTY"),("select","^((optgroup)|(option))+$","(optgroup|option)+"),("optgroup","^((option))+$","(option)+"),("option","^(PCDATA)$","(#PCDATA)"),("textarea","^(PCDATA)$","(#PCDATA)"),("fieldset","^(PCDATA|(legend)|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|legend|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("legend","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("button","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(table)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|table|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|noscript|ins|del|script)*"),("table","^((caption)?((col)*|(colgroup)*)(thead)?(tfoot)?((tbody)+|(tr)+))$","(caption?,(col*|colgroup*),thead?,tfoot?,(tbody+|tr+))"),("caption","^(PCDATA|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("thead","^((tr))+$","(tr)+"),("tfoot","^((tr))+$","(tr)+"),("tbody","^((tr))+$","(tr)+"),("colgroup","^((col))*$","(col)*"),("col","^EMPTY$","EMPTY"),("tr","^((th)|(td))+$","(th|td)+"),("th","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("td","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*$","(#PCDATA|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*")] -- 'childErrors' will return any child ordering errors for any html node. If no errors are found an empty list is returned, otherwise -- a list of errors in String form is returned. Recursively scans down children, so providing the entire page will return all errors. -- > childErrors (_html []) -- > = ["'html' tag error due to children: . Must fit (head,body)"] -- Returns an error because no children were declared for the html tag where and must be children in that order. childErrors :: TagChildren a => a -> [String] childErrors a = childErrorsHelp (tagChildren a) gettag :: [(String,String,String)] -> String -> (String,String,String) gettag [] _ = ("","","") gettag ((t,regex,raw):xs) m | t == m = (t,regex,raw) | otherwise = gettag xs m validate :: (String,[String]) -> Bool validate (tag,children) = (concat children) =~ regex where (t,regex,raw) = gettag allowchildren tag childErrorsHelp :: [(String,[String])] -> [String] childErrorsHelp [] = [] childErrorsHelp ((tag,children):xs) | validate (tag,children) = childErrorsHelp xs | otherwise = ("'" ++ tag ++ "' tag error due to children: " ++ (concat (intersperse "-" children)) ++ ". Must fit " ++ raw):(childErrorsHelp xs) where (t,regex,raw) = gettag allowchildren tag 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,6)],[(2,2),(3,99999),(4,99999),(5,99999),(6,2),(7,2),(52,3)],[(77,99999)],[(7,2),(8,6),(10,38),(11,30),(12,30),(13,30),(14,30),(15,30),(16,30),(17,30),(18,7),(19,7),(21,8),(24,30),(25,99999),(26,39),(27,6),(28,38),(29,38),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,3),(53,99999),(54,99999),(55,19),(57,10),(58,31),(59,99999),(60,27),(63,2),(64,47),(66,29),(67,13),(77,99999)],[(7,2),(28,5),(29,5),(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,18),(54,99999),(55,19),(58,20),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,6),(10,5),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,6),(28,5),(29,5),(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,18),(54,99999),(55,19),(57,10),(58,20),(59,99999),(60,27),(63,2),(64,17),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,5),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,6),(28,5),(29,5),(57,10),(64,17),(67,13)],[(20,5)],[(22,4),(23,5)],[(7,2),(28,5),(29,5),(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,19),(58,20),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,10),(10,11),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,10),(28,11),(29,11),(64,12),(67,13)],[(7,2),(8,10),(10,11),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,10),(28,11),(29,11),(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,41),(54,99999),(55,42),(58,20),(59,99999),(60,27),(63,2),(64,12),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,11),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,10),(28,11),(29,11),(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,41),(54,99999),(55,42),(58,20),(59,99999),(60,27),(63,2),(64,12),(65,4),(66,29),(67,13),(77,99999)],[(68,4),(69,14),(70,14),(71,14),(72,15),(73,99999),(74,16)],[(74,16)],[(73,99999)],[(75,11),(76,11)],[(7,2),(8,6),(10,5),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,6),(28,5),(29,5),(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,18),(54,99999),(55,19),(57,10),(58,20),(59,99999),(60,27),(63,2),(64,17),(65,4),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,5),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,6),(28,5),(29,5),(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,18),(53,99999),(54,99999),(55,19),(57,10),(58,20),(59,99999),(60,27),(63,2),(64,17),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,5),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,6),(28,5),(29,5),(56,99999),(57,10),(64,17),(67,13)],[(7,2),(28,21),(29,21),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,26),(54,99999),(55,19),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,6),(10,21),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,6),(28,21),(29,21),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,26),(54,99999),(55,19),(57,10),(59,99999),(60,27),(63,2),(64,25),(66,29),(67,13),(77,99999)],[(7,2),(28,21),(29,21),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(55,19),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,10),(10,23),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,10),(28,23),(29,23),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,43),(54,99999),(55,42),(59,99999),(60,27),(63,2),(64,24),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,23),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,10),(28,23),(29,23),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,43),(54,99999),(55,42),(59,99999),(60,27),(63,2),(64,24),(65,20),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,21),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,6),(28,21),(29,21),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,26),(54,99999),(55,19),(57,10),(59,99999),(60,27),(63,2),(64,25),(65,20),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,21),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,6),(28,21),(29,21),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,26),(53,99999),(54,99999),(55,19),(57,10),(59,99999),(60,27),(63,2),(64,25),(66,29),(67,13),(77,99999)],[(61,28),(62,2)],[(62,2)],[(7,2),(8,6),(10,21),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,6),(28,21),(29,21),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,26),(54,99999),(55,19),(67,13),(77,99999)],[(7,2),(28,38),(29,38),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,3),(54,99999),(55,19),(58,31),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(28,32),(29,32),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,37),(54,99999),(55,19),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,6),(10,32),(11,31),(12,31),(13,31),(14,31),(15,31),(16,31),(17,31),(18,7),(19,7),(21,8),(24,31),(25,99999),(26,33),(27,6),(28,32),(29,32),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,37),(54,99999),(55,19),(57,10),(59,99999),(60,27),(63,2),(64,36),(66,29),(67,13),(77,99999)],[(7,2),(28,32),(29,32),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(55,19),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,10),(10,34),(11,31),(12,31),(13,31),(14,31),(15,31),(16,31),(17,31),(18,7),(19,7),(21,8),(24,31),(25,99999),(26,33),(27,10),(28,34),(29,34),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,45),(54,99999),(55,42),(59,99999),(60,27),(63,2),(64,35),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,34),(11,31),(12,31),(13,31),(14,31),(15,31),(16,31),(17,31),(18,7),(19,7),(21,8),(24,31),(25,99999),(26,33),(27,10),(28,34),(29,34),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,45),(54,99999),(55,42),(59,99999),(60,27),(63,2),(64,35),(65,31),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,32),(11,31),(12,31),(13,31),(14,31),(15,31),(16,31),(17,31),(18,7),(19,7),(21,8),(24,31),(25,99999),(26,33),(27,6),(28,32),(29,32),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,37),(54,99999),(55,19),(57,10),(59,99999),(60,27),(63,2),(64,36),(65,31),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,32),(11,31),(12,31),(13,31),(14,31),(15,31),(16,31),(17,31),(18,7),(19,7),(21,8),(24,31),(25,99999),(26,33),(27,6),(28,32),(29,32),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,37),(53,99999),(54,99999),(55,19),(57,10),(59,99999),(60,27),(63,2),(64,36),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,38),(11,30),(12,30),(13,30),(14,30),(15,30),(16,30),(17,30),(18,7),(19,7),(21,8),(24,30),(25,99999),(26,39),(27,6),(28,38),(29,38),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,3),(54,99999),(55,19),(57,10),(58,31),(59,99999),(60,27),(63,2),(64,47),(66,29),(67,13),(77,99999)],[(7,2),(28,38),(29,38),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(55,19),(58,31),(59,99999),(60,27),(63,2),(66,29),(77,99999)],[(7,2),(8,10),(10,40),(11,30),(12,30),(13,30),(14,30),(15,30),(16,30),(17,30),(18,7),(19,7),(21,8),(24,30),(25,99999),(26,39),(27,10),(28,40),(29,40),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,44),(54,99999),(55,42),(58,31),(59,99999),(60,27),(63,2),(64,46),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,11),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,10),(28,11),(29,11),(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,41),(53,99999),(54,99999),(55,42),(58,20),(59,99999),(60,27),(63,2),(64,12),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,11),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,7),(19,7),(21,8),(24,4),(25,99999),(26,9),(27,10),(28,11),(29,11),(56,99999),(64,12),(67,13)],[(7,2),(8,10),(10,23),(11,20),(12,20),(13,20),(14,20),(15,20),(16,20),(17,20),(18,7),(19,7),(21,8),(24,20),(25,99999),(26,22),(27,10),(28,23),(29,23),(31,20),(32,20),(33,99999),(34,20),(35,20),(36,20),(37,20),(38,20),(39,20),(40,20),(41,20),(42,20),(43,20),(44,20),(45,20),(46,20),(47,20),(48,20),(49,20),(50,20),(51,20),(52,43),(53,99999),(54,99999),(55,42),(59,99999),(60,27),(63,2),(64,24),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,40),(11,30),(12,30),(13,30),(14,30),(15,30),(16,30),(17,30),(18,7),(19,7),(21,8),(24,30),(25,99999),(26,39),(27,10),(28,40),(29,40),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,44),(53,99999),(54,99999),(55,42),(58,31),(59,99999),(60,27),(63,2),(64,46),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,34),(11,31),(12,31),(13,31),(14,31),(15,31),(16,31),(17,31),(18,7),(19,7),(21,8),(24,31),(25,99999),(26,33),(27,10),(28,34),(29,34),(30,20),(31,31),(32,31),(33,99999),(34,31),(35,31),(36,31),(37,31),(38,31),(39,31),(40,31),(41,31),(42,31),(43,31),(44,31),(45,31),(46,31),(47,31),(48,31),(49,31),(50,31),(51,31),(52,45),(53,99999),(54,99999),(55,42),(59,99999),(60,27),(63,2),(64,35),(66,29),(67,13),(77,99999)],[(7,2),(8,10),(10,40),(11,30),(12,30),(13,30),(14,30),(15,30),(16,30),(17,30),(18,7),(19,7),(21,8),(24,30),(25,99999),(26,39),(27,10),(28,40),(29,40),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,44),(54,99999),(55,42),(58,31),(59,99999),(60,27),(63,2),(64,46),(65,30),(66,29),(67,13),(77,99999)],[(7,2),(8,6),(10,38),(11,30),(12,30),(13,30),(14,30),(15,30),(16,30),(17,30),(18,7),(19,7),(21,8),(24,30),(25,99999),(26,39),(27,6),(28,38),(29,38),(30,4),(31,30),(32,30),(33,99999),(34,30),(35,30),(36,30),(37,30),(38,30),(39,30),(40,30),(41,30),(42,30),(43,30),(44,30),(45,30),(46,30),(47,30),(48,30),(49,30),(50,30),(51,30),(52,3),(54,99999),(55,19),(57,10),(58,31),(59,99999),(60,27),(63,2),(64,47),(65,30),(66,29),(67,13),(77,99999)],[]] -- | '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" ],["No attributes"]] | n == 99999 && xs == [] = [[x ++ " can not contain any inner nodes"], sort(map (\a->a++"_att") (attList !! (snd (tagList !! (toNdx x)))))] | n == 99999 = [[x ++ " can not contain any inner nodes"], []] | 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)