{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-} -- | -- Module : Text.CHXHtml.XHtml1_frameset -- 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_frameset( -- * 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_ ,_applet ,applet_ ,_area ,area_ ,_b ,b_ ,_base ,base_ ,_basefont ,basefont_ ,_bdo ,bdo_ ,_big ,big_ ,_blockquote ,blockquote_ ,_body ,body_ ,_br ,br_ ,_button ,button_ ,_caption ,caption_ ,_center ,center_ ,_cite ,cite_ ,_code ,code_ ,_col ,col_ ,_colgroup ,colgroup_ ,_dd ,dd_ ,_del ,del_ ,_dfn ,dfn_ ,_dir ,dir_ ,_div ,div_ ,_dl ,dl_ ,_dt ,dt_ ,_em ,em_ ,_fieldset ,fieldset_ ,_font ,font_ ,_form ,form_ ,_frame ,frame_ ,_frameset ,frameset_ ,_h1 ,h1_ ,_h2 ,h2_ ,_h3 ,h3_ ,_h4 ,h4_ ,_h5 ,h5_ ,_h6 ,h6_ ,_head ,head_ ,_hr ,hr_ ,_i ,i_ ,_iframe ,iframe_ ,_img ,img_ ,_input ,input_ ,_ins ,ins_ ,_isindex ,isindex_ ,_kbd ,kbd_ ,_label ,label_ ,_legend ,legend_ ,_li ,li_ ,_link ,link_ ,_map ,map_ ,_menu ,menu_ ,_meta ,meta_ ,_noframes ,noframes_ ,_noscript ,noscript_ ,_object ,object_ ,_ol ,ol_ ,_optgroup ,optgroup_ ,_option ,option_ ,_p ,p_ ,_param ,param_ ,_pre ,pre_ ,_q ,q_ ,_s ,s_ ,_samp ,samp_ ,_script ,script_ ,_select ,select_ ,_small ,small_ ,_span ,span_ ,_strike ,strike_ ,_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_ ,_u ,u_ ,_ul ,ul_ ,_var ,var_ , -- * Attributes http_equiv_att, http_equiv_att_bs,nohref_att, onkeydown_att, onkeydown_att_bs,target_att, target_att_bs,onkeyup_att, onkeyup_att_bs,onreset_att, onreset_att_bs,code_att, code_att_bs,valign_att, name_att, name_att_bs,charset_att, charset_att_bs,prompt_att, prompt_att_bs,accept_charset_att, accept_charset_att_bs,rev_att, rev_att_bs,title_att, title_att_bs,start_att, start_att_bs,enctype_att, enctype_att_bs,usemap_att, usemap_att_bs,nowrap_att, coords_att, coords_att_bs,onblur_att, onblur_att_bs,datetime_att, datetime_att_bs,dir_att, color_att, color_att_bs,vspace_att, vspace_att_bs,background_att, background_att_bs,height_att, height_att_bs,char_att, char_att_bs,codebase_att, codebase_att_bs,profile_att, profile_att_bs,rel_att, rel_att_bs,onsubmit_att, onsubmit_att_bs,marginwidth_att, marginwidth_att_bs,abbr_att, abbr_att_bs,onchange_att, onchange_att_bs,href_att, href_att_bs,id_att, id_att_bs,value_att, value_att_bs,data_att, data_att_bs,declare_att, type_att, type_att_bs,headers_att, headers_att_bs,object_att, object_att_bs,noresize_att, rowspan_att, rowspan_att_bs,defer_att, cellspacing_att, cellspacing_att_bs,charoff_att, charoff_att_bs,accept_att, accept_att_bs,alt_att, alt_att_bs,onmouseout_att, onmouseout_att_bs,border_att, border_att_bs,onunload_att, onunload_att_bs,cellpadding_att, cellpadding_att_bs,valuetype_att, content_att, content_att_bs,clear_att, onmouseup_att, onmouseup_att_bs,scope_att, onmouseover_att, onmouseover_att_bs,lang_att, lang_att_bs,align_att, scheme_att, scheme_att_bs,frameborder_att, onmousedown_att, onmousedown_att_bs,onclick_att, onclick_att_bs,span_att, span_att_bs,width_att, width_att_bs,vlink_att, vlink_att_bs,ismap_att, frame_att, size_att, size_att_bs,face_att, face_att_bs,bgcolor_att, bgcolor_att_bs,summary_att, summary_att_bs,text_att, text_att_bs,method_att, language_att, language_att_bs,tabindex_att, tabindex_att_bs,standby_att, standby_att_bs,onmousemove_att, onmousemove_att_bs,style_att, style_att_bs,codetype_att, codetype_att_bs,multiple_att, xmlns_att, xmlns_att_bs,ondblclick_att, ondblclick_att_bs,axis_att, axis_att_bs,cols_att, cols_att_bs,readonly_att, media_att, media_att_bs,compact_att, src_att, src_att_bs,for_att, for_att_bs,hreflang_att, hreflang_att_bs,checked_att, onkeypress_att, onkeypress_att_bs,class_att, class_att_bs,shape_att, label_att, label_att_bs,accesskey_att, accesskey_att_bs,disabled_att, scrolling_att, rows_att, rows_att_bs,rules_att, onfocus_att, onfocus_att_bs,alink_att, alink_att_bs,colspan_att, colspan_att_bs,cite_att, cite_att_bs,marginheight_att, marginheight_att_bs,link_att, link_att_bs,maxlength_att, maxlength_att_bs,onselect_att, onselect_att_bs,archive_att, archive_att_bs,longdesc_att, longdesc_att_bs,classid_att, classid_att_bs,space_att, noshade_att, hspace_att, hspace_att_bs,onload_att, onload_att_bs,action_att, action_att_bs,selected_att, -- ** Enumerated Attribute Values RulesEnum(..),ScrollingEnum(..),ShapeEnum(..),MethodEnum(..),FrameEnum(..),FrameborderEnum(..),AlignEnum(..),ScopeEnum(..),ClearEnum(..),ValuetypeEnum(..),DirEnum(..),ValignEnum(..), ) 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 Att61 = Id_Att_61 B.ByteString | Class_Att_61 B.ByteString | Style_Att_61 B.ByteString | Title_Att_61 B.ByteString | Lang_Att_61 B.ByteString | Dir_Att_61 B.ByteString | Onclick_Att_61 B.ByteString | Ondblclick_Att_61 B.ByteString | Onmousedown_Att_61 B.ByteString | Onmouseup_Att_61 B.ByteString | Onmouseover_Att_61 B.ByteString | Onmousemove_Att_61 B.ByteString | Onmouseout_Att_61 B.ByteString | Onkeypress_Att_61 B.ByteString | Onkeydown_Att_61 B.ByteString | Onkeyup_Att_61 B.ByteString | Abbr_Att_61 B.ByteString | Axis_Att_61 B.ByteString | Headers_Att_61 B.ByteString | Scope_Att_61 B.ByteString | Rowspan_Att_61 B.ByteString | Colspan_Att_61 B.ByteString | Align_Att_61 B.ByteString | Char_Att_61 B.ByteString | Charoff_Att_61 B.ByteString | Valign_Att_61 B.ByteString | Nowrap_Att_61 B.ByteString | Bgcolor_Att_61 B.ByteString | Width_Att_61 B.ByteString | Height_Att_61 B.ByteString deriving (Show) data Att60 = Id_Att_60 B.ByteString | Class_Att_60 B.ByteString | Style_Att_60 B.ByteString | Title_Att_60 B.ByteString | Lang_Att_60 B.ByteString | Dir_Att_60 B.ByteString | Onclick_Att_60 B.ByteString | Ondblclick_Att_60 B.ByteString | Onmousedown_Att_60 B.ByteString | Onmouseup_Att_60 B.ByteString | Onmouseover_Att_60 B.ByteString | Onmousemove_Att_60 B.ByteString | Onmouseout_Att_60 B.ByteString | Onkeypress_Att_60 B.ByteString | Onkeydown_Att_60 B.ByteString | Onkeyup_Att_60 B.ByteString | Align_Att_60 B.ByteString | Char_Att_60 B.ByteString | Charoff_Att_60 B.ByteString | Valign_Att_60 B.ByteString | Bgcolor_Att_60 B.ByteString deriving (Show) data Att59 = Id_Att_59 B.ByteString | Class_Att_59 B.ByteString | Style_Att_59 B.ByteString | Title_Att_59 B.ByteString | Lang_Att_59 B.ByteString | Dir_Att_59 B.ByteString | Onclick_Att_59 B.ByteString | Ondblclick_Att_59 B.ByteString | Onmousedown_Att_59 B.ByteString | Onmouseup_Att_59 B.ByteString | Onmouseover_Att_59 B.ByteString | Onmousemove_Att_59 B.ByteString | Onmouseout_Att_59 B.ByteString | Onkeypress_Att_59 B.ByteString | Onkeydown_Att_59 B.ByteString | Onkeyup_Att_59 B.ByteString | Span_Att_59 B.ByteString | Width_Att_59 B.ByteString | Align_Att_59 B.ByteString | Char_Att_59 B.ByteString | Charoff_Att_59 B.ByteString | Valign_Att_59 B.ByteString deriving (Show) data Att58 = Id_Att_58 B.ByteString | Class_Att_58 B.ByteString | Style_Att_58 B.ByteString | Title_Att_58 B.ByteString | Lang_Att_58 B.ByteString | Dir_Att_58 B.ByteString | Onclick_Att_58 B.ByteString | Ondblclick_Att_58 B.ByteString | Onmousedown_Att_58 B.ByteString | Onmouseup_Att_58 B.ByteString | Onmouseover_Att_58 B.ByteString | Onmousemove_Att_58 B.ByteString | Onmouseout_Att_58 B.ByteString | Onkeypress_Att_58 B.ByteString | Onkeydown_Att_58 B.ByteString | Onkeyup_Att_58 B.ByteString | Align_Att_58 B.ByteString | Char_Att_58 B.ByteString | Charoff_Att_58 B.ByteString | Valign_Att_58 B.ByteString deriving (Show) data Att57 = Id_Att_57 B.ByteString | Class_Att_57 B.ByteString | Style_Att_57 B.ByteString | Title_Att_57 B.ByteString | Lang_Att_57 B.ByteString | Dir_Att_57 B.ByteString | Onclick_Att_57 B.ByteString | Ondblclick_Att_57 B.ByteString | Onmousedown_Att_57 B.ByteString | Onmouseup_Att_57 B.ByteString | Onmouseover_Att_57 B.ByteString | Onmousemove_Att_57 B.ByteString | Onmouseout_Att_57 B.ByteString | Onkeypress_Att_57 B.ByteString | Onkeydown_Att_57 B.ByteString | Onkeyup_Att_57 B.ByteString | Summary_Att_57 B.ByteString | Width_Att_57 B.ByteString | Border_Att_57 B.ByteString | Frame_Att_57 B.ByteString | Rules_Att_57 B.ByteString | Cellspacing_Att_57 B.ByteString | Cellpadding_Att_57 B.ByteString | Align_Att_57 B.ByteString | Bgcolor_Att_57 B.ByteString deriving (Show) data Att56 = Id_Att_56 B.ByteString | Class_Att_56 B.ByteString | Style_Att_56 B.ByteString | Title_Att_56 B.ByteString | Lang_Att_56 B.ByteString | Dir_Att_56 B.ByteString | Prompt_Att_56 B.ByteString deriving (Show) data Att55 = Id_Att_55 B.ByteString | Class_Att_55 B.ByteString | Style_Att_55 B.ByteString | Title_Att_55 B.ByteString | Lang_Att_55 B.ByteString | Dir_Att_55 B.ByteString | Onclick_Att_55 B.ByteString | Ondblclick_Att_55 B.ByteString | Onmousedown_Att_55 B.ByteString | Onmouseup_Att_55 B.ByteString | Onmouseover_Att_55 B.ByteString | Onmousemove_Att_55 B.ByteString | Onmouseout_Att_55 B.ByteString | Onkeypress_Att_55 B.ByteString | Onkeydown_Att_55 B.ByteString | Onkeyup_Att_55 B.ByteString | Accesskey_Att_55 B.ByteString | Tabindex_Att_55 B.ByteString | Onfocus_Att_55 B.ByteString | Onblur_Att_55 B.ByteString | Name_Att_55 B.ByteString | Value_Att_55 B.ByteString | Type_Att_55 B.ByteString | Disabled_Att_55 B.ByteString deriving (Show) data Att54 = Id_Att_54 B.ByteString | Class_Att_54 B.ByteString | Style_Att_54 B.ByteString | Title_Att_54 B.ByteString | Lang_Att_54 B.ByteString | Dir_Att_54 B.ByteString | Onclick_Att_54 B.ByteString | Ondblclick_Att_54 B.ByteString | Onmousedown_Att_54 B.ByteString | Onmouseup_Att_54 B.ByteString | Onmouseover_Att_54 B.ByteString | Onmousemove_Att_54 B.ByteString | Onmouseout_Att_54 B.ByteString | Onkeypress_Att_54 B.ByteString | Onkeydown_Att_54 B.ByteString | Onkeyup_Att_54 B.ByteString | Accesskey_Att_54 B.ByteString | Align_Att_54 B.ByteString deriving (Show) data Att53 = Cols_Att_53 B.ByteString deriving (Show) data Att52 = Rows_Att_52 B.ByteString deriving (Show) data Att51 = Id_Att_51 B.ByteString | Class_Att_51 B.ByteString | Style_Att_51 B.ByteString | Title_Att_51 B.ByteString | Lang_Att_51 B.ByteString | Dir_Att_51 B.ByteString | Onclick_Att_51 B.ByteString | Ondblclick_Att_51 B.ByteString | Onmousedown_Att_51 B.ByteString | Onmouseup_Att_51 B.ByteString | Onmouseover_Att_51 B.ByteString | Onmousemove_Att_51 B.ByteString | Onmouseout_Att_51 B.ByteString | Onkeypress_Att_51 B.ByteString | Onkeydown_Att_51 B.ByteString | Onkeyup_Att_51 B.ByteString | Accesskey_Att_51 B.ByteString | Tabindex_Att_51 B.ByteString | Onfocus_Att_51 B.ByteString | Onblur_Att_51 B.ByteString | Name_Att_51 B.ByteString | Rows_Att_51 B.ByteString | Cols_Att_51 B.ByteString | Disabled_Att_51 B.ByteString | Readonly_Att_51 B.ByteString | Onselect_Att_51 B.ByteString | Onchange_Att_51 B.ByteString deriving (Show) data Att50 = Id_Att_50 B.ByteString | Class_Att_50 B.ByteString | Style_Att_50 B.ByteString | Title_Att_50 B.ByteString | Lang_Att_50 B.ByteString | Dir_Att_50 B.ByteString | Onclick_Att_50 B.ByteString | Ondblclick_Att_50 B.ByteString | Onmousedown_Att_50 B.ByteString | Onmouseup_Att_50 B.ByteString | Onmouseover_Att_50 B.ByteString | Onmousemove_Att_50 B.ByteString | Onmouseout_Att_50 B.ByteString | Onkeypress_Att_50 B.ByteString | Onkeydown_Att_50 B.ByteString | Onkeyup_Att_50 B.ByteString | Selected_Att_50 B.ByteString | Disabled_Att_50 B.ByteString | Label_Att_50 B.ByteString | Value_Att_50 B.ByteString deriving (Show) data Att49 = Label_Att_49 B.ByteString deriving (Show) data Att48 = Id_Att_48 B.ByteString | Class_Att_48 B.ByteString | Style_Att_48 B.ByteString | Title_Att_48 B.ByteString | Lang_Att_48 B.ByteString | Dir_Att_48 B.ByteString | Onclick_Att_48 B.ByteString | Ondblclick_Att_48 B.ByteString | Onmousedown_Att_48 B.ByteString | Onmouseup_Att_48 B.ByteString | Onmouseover_Att_48 B.ByteString | Onmousemove_Att_48 B.ByteString | Onmouseout_Att_48 B.ByteString | Onkeypress_Att_48 B.ByteString | Onkeydown_Att_48 B.ByteString | Onkeyup_Att_48 B.ByteString | Disabled_Att_48 B.ByteString | Label_Att_48 B.ByteString deriving (Show) data Att47 = Id_Att_47 B.ByteString | Class_Att_47 B.ByteString | Style_Att_47 B.ByteString | Title_Att_47 B.ByteString | Lang_Att_47 B.ByteString | Dir_Att_47 B.ByteString | Onclick_Att_47 B.ByteString | Ondblclick_Att_47 B.ByteString | Onmousedown_Att_47 B.ByteString | Onmouseup_Att_47 B.ByteString | Onmouseover_Att_47 B.ByteString | Onmousemove_Att_47 B.ByteString | Onmouseout_Att_47 B.ByteString | Onkeypress_Att_47 B.ByteString | Onkeydown_Att_47 B.ByteString | Onkeyup_Att_47 B.ByteString | Name_Att_47 B.ByteString | Size_Att_47 B.ByteString | Multiple_Att_47 B.ByteString | Disabled_Att_47 B.ByteString | Tabindex_Att_47 B.ByteString | Onfocus_Att_47 B.ByteString | Onblur_Att_47 B.ByteString | Onchange_Att_47 B.ByteString deriving (Show) data Att46 = Id_Att_46 B.ByteString | Class_Att_46 B.ByteString | Style_Att_46 B.ByteString | Title_Att_46 B.ByteString | Lang_Att_46 B.ByteString | Dir_Att_46 B.ByteString | Onclick_Att_46 B.ByteString | Ondblclick_Att_46 B.ByteString | Onmousedown_Att_46 B.ByteString | Onmouseup_Att_46 B.ByteString | Onmouseover_Att_46 B.ByteString | Onmousemove_Att_46 B.ByteString | Onmouseout_Att_46 B.ByteString | Onkeypress_Att_46 B.ByteString | Onkeydown_Att_46 B.ByteString | Onkeyup_Att_46 B.ByteString | Accesskey_Att_46 B.ByteString | Tabindex_Att_46 B.ByteString | Onfocus_Att_46 B.ByteString | Onblur_Att_46 B.ByteString | Type_Att_46 B.ByteString | Name_Att_46 B.ByteString | Value_Att_46 B.ByteString | Checked_Att_46 B.ByteString | Disabled_Att_46 B.ByteString | Readonly_Att_46 B.ByteString | Size_Att_46 B.ByteString | Maxlength_Att_46 B.ByteString | Src_Att_46 B.ByteString | Alt_Att_46 B.ByteString | Usemap_Att_46 B.ByteString | Onselect_Att_46 B.ByteString | Onchange_Att_46 B.ByteString | Accept_Att_46 B.ByteString | Align_Att_46 B.ByteString deriving (Show) data Att45 = Id_Att_45 B.ByteString | Class_Att_45 B.ByteString | Style_Att_45 B.ByteString | Title_Att_45 B.ByteString | Lang_Att_45 B.ByteString | Dir_Att_45 B.ByteString | Onclick_Att_45 B.ByteString | Ondblclick_Att_45 B.ByteString | Onmousedown_Att_45 B.ByteString | Onmouseup_Att_45 B.ByteString | Onmouseover_Att_45 B.ByteString | Onmousemove_Att_45 B.ByteString | Onmouseout_Att_45 B.ByteString | Onkeypress_Att_45 B.ByteString | Onkeydown_Att_45 B.ByteString | Onkeyup_Att_45 B.ByteString | For_Att_45 B.ByteString | Accesskey_Att_45 B.ByteString | Onfocus_Att_45 B.ByteString | Onblur_Att_45 B.ByteString deriving (Show) data Att44 = Action_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 | Action_Att_43 B.ByteString | Method_Att_43 B.ByteString | Name_Att_43 B.ByteString | Enctype_Att_43 B.ByteString | Onsubmit_Att_43 B.ByteString | Onreset_Att_43 B.ByteString | Accept_Att_43 B.ByteString | Accept_charset_Att_43 B.ByteString | Target_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 | Accesskey_Att_42 B.ByteString | Tabindex_Att_42 B.ByteString | Onfocus_Att_42 B.ByteString | Onblur_Att_42 B.ByteString | Shape_Att_42 B.ByteString | Coords_Att_42 B.ByteString | Href_Att_42 B.ByteString | Nohref_Att_42 B.ByteString | Alt_Att_42 B.ByteString | Target_Att_42 B.ByteString deriving (Show) data Att41 = Id_Att_41 B.ByteString deriving (Show) data Att40 = 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 | Id_Att_40 B.ByteString | Class_Att_40 B.ByteString | Style_Att_40 B.ByteString | Title_Att_40 B.ByteString | Name_Att_40 B.ByteString deriving (Show) data Att39 = Alt_Att_39 B.ByteString deriving (Show) data Att38 = Src_Att_38 B.ByteString deriving (Show) data Att37 = Id_Att_37 B.ByteString | Class_Att_37 B.ByteString | Style_Att_37 B.ByteString | Title_Att_37 B.ByteString | Lang_Att_37 B.ByteString | Dir_Att_37 B.ByteString | Onclick_Att_37 B.ByteString | Ondblclick_Att_37 B.ByteString | Onmousedown_Att_37 B.ByteString | Onmouseup_Att_37 B.ByteString | Onmouseover_Att_37 B.ByteString | Onmousemove_Att_37 B.ByteString | Onmouseout_Att_37 B.ByteString | Onkeypress_Att_37 B.ByteString | Onkeydown_Att_37 B.ByteString | Onkeyup_Att_37 B.ByteString | Src_Att_37 B.ByteString | Alt_Att_37 B.ByteString | Name_Att_37 B.ByteString | Longdesc_Att_37 B.ByteString | Height_Att_37 B.ByteString | Width_Att_37 B.ByteString | Usemap_Att_37 B.ByteString | Ismap_Att_37 B.ByteString | Align_Att_37 B.ByteString | Border_Att_37 B.ByteString | Hspace_Att_37 B.ByteString | Vspace_Att_37 B.ByteString deriving (Show) data Att36 = Height_Att_36 B.ByteString deriving (Show) data Att35 = Width_Att_35 B.ByteString deriving (Show) data Att34 = Id_Att_34 B.ByteString | Class_Att_34 B.ByteString | Style_Att_34 B.ByteString | Title_Att_34 B.ByteString | Codebase_Att_34 B.ByteString | Archive_Att_34 B.ByteString | Code_Att_34 B.ByteString | Object_Att_34 B.ByteString | Alt_Att_34 B.ByteString | Name_Att_34 B.ByteString | Width_Att_34 B.ByteString | Height_Att_34 B.ByteString | Align_Att_34 B.ByteString | Hspace_Att_34 B.ByteString | Vspace_Att_34 B.ByteString deriving (Show) data Att33 = Name_Att_33 B.ByteString deriving (Show) data Att32 = Id_Att_32 B.ByteString | Name_Att_32 B.ByteString | Value_Att_32 B.ByteString | Valuetype_Att_32 B.ByteString | Type_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 | Declare_Att_31 B.ByteString | Classid_Att_31 B.ByteString | Codebase_Att_31 B.ByteString | Data_Att_31 B.ByteString | Type_Att_31 B.ByteString | Codetype_Att_31 B.ByteString | Archive_Att_31 B.ByteString | Standby_Att_31 B.ByteString | Height_Att_31 B.ByteString | Width_Att_31 B.ByteString | Usemap_Att_31 B.ByteString | Name_Att_31 B.ByteString | Tabindex_Att_31 B.ByteString | Align_Att_31 B.ByteString | Border_Att_31 B.ByteString | Hspace_Att_31 B.ByteString | Vspace_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 | Size_Att_30 B.ByteString | Color_Att_30 B.ByteString | Face_Att_30 B.ByteString deriving (Show) data Att29 = Size_Att_29 B.ByteString deriving (Show) data Att28 = Id_Att_28 B.ByteString | Size_Att_28 B.ByteString | Color_Att_28 B.ByteString | Face_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 | Clear_Att_27 B.ByteString deriving (Show) data Att26 = Dir_Att_26 B.ByteString deriving (Show) data Att25 = Id_Att_25 B.ByteString | Class_Att_25 B.ByteString | Style_Att_25 B.ByteString | Title_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 | Lang_Att_25 B.ByteString | Dir_Att_25 B.ByteString deriving (Show) data Att24 = Id_Att_24 B.ByteString | Class_Att_24 B.ByteString | Style_Att_24 B.ByteString | Title_Att_24 B.ByteString | Lang_Att_24 B.ByteString | Dir_Att_24 B.ByteString | Onclick_Att_24 B.ByteString | Ondblclick_Att_24 B.ByteString | Onmousedown_Att_24 B.ByteString | Onmouseup_Att_24 B.ByteString | Onmouseover_Att_24 B.ByteString | Onmousemove_Att_24 B.ByteString | Onmouseout_Att_24 B.ByteString | Onkeypress_Att_24 B.ByteString | Onkeydown_Att_24 B.ByteString | Onkeyup_Att_24 B.ByteString | Accesskey_Att_24 B.ByteString | Tabindex_Att_24 B.ByteString | Onfocus_Att_24 B.ByteString | Onblur_Att_24 B.ByteString | Charset_Att_24 B.ByteString | Type_Att_24 B.ByteString | Name_Att_24 B.ByteString | Href_Att_24 B.ByteString | Hreflang_Att_24 B.ByteString | Rel_Att_24 B.ByteString | Rev_Att_24 B.ByteString | Shape_Att_24 B.ByteString | Coords_Att_24 B.ByteString | Target_Att_24 B.ByteString deriving (Show) data Att23 = Id_Att_23 B.ByteString | Class_Att_23 B.ByteString | Style_Att_23 B.ByteString | Title_Att_23 B.ByteString | Lang_Att_23 B.ByteString | Dir_Att_23 B.ByteString | Onclick_Att_23 B.ByteString | Ondblclick_Att_23 B.ByteString | Onmousedown_Att_23 B.ByteString | Onmouseup_Att_23 B.ByteString | Onmouseover_Att_23 B.ByteString | Onmousemove_Att_23 B.ByteString | Onmouseout_Att_23 B.ByteString | Onkeypress_Att_23 B.ByteString | Onkeydown_Att_23 B.ByteString | Onkeyup_Att_23 B.ByteString | Cite_Att_23 B.ByteString | Datetime_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 | Cite_Att_22 B.ByteString deriving (Show) data Att21 = Id_Att_21 B.ByteString | Class_Att_21 B.ByteString | Style_Att_21 B.ByteString | Title_Att_21 B.ByteString | Lang_Att_21 B.ByteString | Dir_Att_21 B.ByteString | Onclick_Att_21 B.ByteString | Ondblclick_Att_21 B.ByteString | Onmousedown_Att_21 B.ByteString | Onmouseup_Att_21 B.ByteString | Onmouseover_Att_21 B.ByteString | Onmousemove_Att_21 B.ByteString | Onmouseout_Att_21 B.ByteString | Onkeypress_Att_21 B.ByteString | Onkeydown_Att_21 B.ByteString | Onkeyup_Att_21 B.ByteString | Width_Att_21 B.ByteString | Space_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 | Align_Att_20 B.ByteString | Noshade_Att_20 B.ByteString | Size_Att_20 B.ByteString | Width_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 | Lang_Att_19 B.ByteString | Dir_Att_19 B.ByteString | Onclick_Att_19 B.ByteString | Ondblclick_Att_19 B.ByteString | Onmousedown_Att_19 B.ByteString | Onmouseup_Att_19 B.ByteString | Onmouseover_Att_19 B.ByteString | Onmousemove_Att_19 B.ByteString | Onmouseout_Att_19 B.ByteString | Onkeypress_Att_19 B.ByteString | Onkeydown_Att_19 B.ByteString | Onkeyup_Att_19 B.ByteString | Type_Att_19 B.ByteString | Value_Att_19 B.ByteString deriving (Show) data Att18 = Id_Att_18 B.ByteString | Class_Att_18 B.ByteString | Style_Att_18 B.ByteString | Title_Att_18 B.ByteString | Lang_Att_18 B.ByteString | Dir_Att_18 B.ByteString | Onclick_Att_18 B.ByteString | Ondblclick_Att_18 B.ByteString | Onmousedown_Att_18 B.ByteString | Onmouseup_Att_18 B.ByteString | Onmouseover_Att_18 B.ByteString | Onmousemove_Att_18 B.ByteString | Onmouseout_Att_18 B.ByteString | Onkeypress_Att_18 B.ByteString | Onkeydown_Att_18 B.ByteString | Onkeyup_Att_18 B.ByteString | Compact_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 | Lang_Att_17 B.ByteString | Dir_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 | Type_Att_17 B.ByteString | Compact_Att_17 B.ByteString | Start_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 | Type_Att_16 B.ByteString | Compact_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 | Align_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 | Onload_Att_14 B.ByteString | Onunload_Att_14 B.ByteString | Background_Att_14 B.ByteString | Bgcolor_Att_14 B.ByteString | Text_Att_14 B.ByteString | Link_Att_14 B.ByteString | Vlink_Att_14 B.ByteString | Alink_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 | Longdesc_Att_13 B.ByteString | Name_Att_13 B.ByteString | Src_Att_13 B.ByteString | Frameborder_Att_13 B.ByteString | Marginwidth_Att_13 B.ByteString | Marginheight_Att_13 B.ByteString | Scrolling_Att_13 B.ByteString | Align_Att_13 B.ByteString | Height_Att_13 B.ByteString | Width_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 | Longdesc_Att_12 B.ByteString | Name_Att_12 B.ByteString | Src_Att_12 B.ByteString | Frameborder_Att_12 B.ByteString | Marginwidth_Att_12 B.ByteString | Marginheight_Att_12 B.ByteString | Noresize_Att_12 B.ByteString | Scrolling_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 | Rows_Att_11 B.ByteString | Cols_Att_11 B.ByteString | Onload_Att_11 B.ByteString | Onunload_Att_11 B.ByteString deriving (Show) data Att10 = Id_Att_10 B.ByteString | Class_Att_10 B.ByteString | Style_Att_10 B.ByteString | Title_Att_10 B.ByteString | Lang_Att_10 B.ByteString | Dir_Att_10 B.ByteString | Onclick_Att_10 B.ByteString | Ondblclick_Att_10 B.ByteString | Onmousedown_Att_10 B.ByteString | Onmouseup_Att_10 B.ByteString | Onmouseover_Att_10 B.ByteString | Onmousemove_Att_10 B.ByteString | Onmouseout_Att_10 B.ByteString | Onkeypress_Att_10 B.ByteString | Onkeydown_Att_10 B.ByteString | Onkeyup_Att_10 B.ByteString deriving (Show) data Att9 = Id_Att_9 B.ByteString | Charset_Att_9 B.ByteString | Type_Att_9 B.ByteString | Language_Att_9 B.ByteString | Src_Att_9 B.ByteString | Defer_Att_9 B.ByteString | Space_Att_9 B.ByteString deriving (Show) data Att8 = Type_Att_8 B.ByteString deriving (Show) data Att7 = Lang_Att_7 B.ByteString | Dir_Att_7 B.ByteString | Id_Att_7 B.ByteString | Type_Att_7 B.ByteString | Media_Att_7 B.ByteString | Title_Att_7 B.ByteString | Space_Att_7 B.ByteString deriving (Show) data Att6 = Id_Att_6 B.ByteString | Class_Att_6 B.ByteString | Style_Att_6 B.ByteString | Title_Att_6 B.ByteString | Lang_Att_6 B.ByteString | Dir_Att_6 B.ByteString | Onclick_Att_6 B.ByteString | Ondblclick_Att_6 B.ByteString | Onmousedown_Att_6 B.ByteString | Onmouseup_Att_6 B.ByteString | Onmouseover_Att_6 B.ByteString | Onmousemove_Att_6 B.ByteString | Onmouseout_Att_6 B.ByteString | Onkeypress_Att_6 B.ByteString | Onkeydown_Att_6 B.ByteString | Onkeyup_Att_6 B.ByteString | Charset_Att_6 B.ByteString | Href_Att_6 B.ByteString | Hreflang_Att_6 B.ByteString | Type_Att_6 B.ByteString | Rel_Att_6 B.ByteString | Rev_Att_6 B.ByteString | Media_Att_6 B.ByteString | Target_Att_6 B.ByteString deriving (Show) data Att5 = Content_Att_5 B.ByteString deriving (Show) data Att4 = Lang_Att_4 B.ByteString | Dir_Att_4 B.ByteString | Id_Att_4 B.ByteString | Http_equiv_Att_4 B.ByteString | Name_Att_4 B.ByteString | Content_Att_4 B.ByteString | Scheme_Att_4 B.ByteString deriving (Show) data Att3 = Id_Att_3 B.ByteString | Href_Att_3 B.ByteString | Target_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 RulesEnum = Rules_none | Groups | Rows | Cols | Rules_all instance Show RulesEnum where show Text.CHXHtml.XHtml1_frameset.Rules_none="none" show Text.CHXHtml.XHtml1_frameset.Groups="groups" show Text.CHXHtml.XHtml1_frameset.Rows="rows" show Text.CHXHtml.XHtml1_frameset.Cols="cols" show Text.CHXHtml.XHtml1_frameset.Rules_all="all" data ScrollingEnum = Yes | No | Auto instance Show ScrollingEnum where show Text.CHXHtml.XHtml1_frameset.Yes="yes" show Text.CHXHtml.XHtml1_frameset.No="no" show Text.CHXHtml.XHtml1_frameset.Auto="auto" data ShapeEnum = Rect | Circle | Poly | Default instance Show ShapeEnum where show Text.CHXHtml.XHtml1_frameset.Rect="rect" show Text.CHXHtml.XHtml1_frameset.Circle="circle" show Text.CHXHtml.XHtml1_frameset.Poly="poly" show Text.CHXHtml.XHtml1_frameset.Default="default" data MethodEnum = Get | Post instance Show MethodEnum where show Text.CHXHtml.XHtml1_frameset.Get="get" show Text.CHXHtml.XHtml1_frameset.Post="post" data FrameEnum = Void | Above | Below | Hsides | Lhs | Rhs | Vsides | Box | Border instance Show FrameEnum where show Text.CHXHtml.XHtml1_frameset.Void="void" show Text.CHXHtml.XHtml1_frameset.Above="above" show Text.CHXHtml.XHtml1_frameset.Below="below" show Text.CHXHtml.XHtml1_frameset.Hsides="hsides" show Text.CHXHtml.XHtml1_frameset.Lhs="lhs" show Text.CHXHtml.XHtml1_frameset.Rhs="rhs" show Text.CHXHtml.XHtml1_frameset.Vsides="vsides" show Text.CHXHtml.XHtml1_frameset.Box="box" show Text.CHXHtml.XHtml1_frameset.Border="border" data FrameborderEnum = D1 | D0 instance Show FrameborderEnum where show Text.CHXHtml.XHtml1_frameset.D1="1" show Text.CHXHtml.XHtml1_frameset.D0="0" data AlignEnum = Align_left | Center | Align_right | Justify instance Show AlignEnum where show Text.CHXHtml.XHtml1_frameset.Align_left="left" show Text.CHXHtml.XHtml1_frameset.Center="center" show Text.CHXHtml.XHtml1_frameset.Align_right="right" show Text.CHXHtml.XHtml1_frameset.Justify="justify" data ScopeEnum = Row | Col | Rowgroup | Colgroup instance Show ScopeEnum where show Text.CHXHtml.XHtml1_frameset.Row="row" show Text.CHXHtml.XHtml1_frameset.Col="col" show Text.CHXHtml.XHtml1_frameset.Rowgroup="rowgroup" show Text.CHXHtml.XHtml1_frameset.Colgroup="colgroup" data ClearEnum = Clear_left | Clear_all | Clear_right | Clear_none instance Show ClearEnum where show Text.CHXHtml.XHtml1_frameset.Clear_left="left" show Text.CHXHtml.XHtml1_frameset.Clear_all="all" show Text.CHXHtml.XHtml1_frameset.Clear_right="right" show Text.CHXHtml.XHtml1_frameset.Clear_none="none" data ValuetypeEnum = Data | Ref | Object instance Show ValuetypeEnum where show Text.CHXHtml.XHtml1_frameset.Data="data" show Text.CHXHtml.XHtml1_frameset.Ref="ref" show Text.CHXHtml.XHtml1_frameset.Object="object" data DirEnum = Ltr | Rtl instance Show DirEnum where show Text.CHXHtml.XHtml1_frameset.Ltr="ltr" show Text.CHXHtml.XHtml1_frameset.Rtl="rtl" data ValignEnum = Top | Middle | Bottom | Baseline instance Show ValignEnum where show Text.CHXHtml.XHtml1_frameset.Top="top" show Text.CHXHtml.XHtml1_frameset.Middle="middle" show Text.CHXHtml.XHtml1_frameset.Bottom="bottom" show Text.CHXHtml.XHtml1_frameset.Baseline="baseline" class A_Http_equiv a where http_equiv_att :: String -> a http_equiv_att_bs :: B.ByteString -> a instance A_Http_equiv Att4 where http_equiv_att s = Http_equiv_Att_4 (s2b_escape s) http_equiv_att_bs = Http_equiv_Att_4 class A_Nohref a where nohref_att :: String -> a instance A_Nohref Att42 where nohref_att s = Nohref_Att_42 (s2b (show s)) class A_Onkeydown a where onkeydown_att :: String -> a onkeydown_att_bs :: B.ByteString -> a instance A_Onkeydown Att61 where onkeydown_att s = Onkeydown_Att_61 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_61 instance A_Onkeydown Att60 where onkeydown_att s = Onkeydown_Att_60 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_60 instance A_Onkeydown Att59 where onkeydown_att s = Onkeydown_Att_59 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_59 instance A_Onkeydown Att58 where onkeydown_att s = Onkeydown_Att_58 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_58 instance A_Onkeydown Att57 where onkeydown_att s = Onkeydown_Att_57 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_57 instance A_Onkeydown Att55 where onkeydown_att s = Onkeydown_Att_55 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_55 instance A_Onkeydown Att54 where onkeydown_att s = Onkeydown_Att_54 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_54 instance A_Onkeydown Att51 where onkeydown_att s = Onkeydown_Att_51 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_51 instance A_Onkeydown Att50 where onkeydown_att s = Onkeydown_Att_50 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_50 instance A_Onkeydown Att48 where onkeydown_att s = Onkeydown_Att_48 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_48 instance A_Onkeydown Att47 where onkeydown_att s = Onkeydown_Att_47 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_47 instance A_Onkeydown Att46 where onkeydown_att s = Onkeydown_Att_46 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_46 instance A_Onkeydown Att45 where onkeydown_att s = Onkeydown_Att_45 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_45 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 Att40 where onkeydown_att s = Onkeydown_Att_40 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_40 instance A_Onkeydown Att37 where onkeydown_att s = Onkeydown_Att_37 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_37 instance A_Onkeydown Att31 where onkeydown_att s = Onkeydown_Att_31 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_31 instance A_Onkeydown Att25 where onkeydown_att s = Onkeydown_Att_25 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_25 instance A_Onkeydown Att24 where onkeydown_att s = Onkeydown_Att_24 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_24 instance A_Onkeydown Att23 where onkeydown_att s = Onkeydown_Att_23 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_23 instance A_Onkeydown Att22 where onkeydown_att s = Onkeydown_Att_22 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_22 instance A_Onkeydown Att21 where onkeydown_att s = Onkeydown_Att_21 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_21 instance A_Onkeydown Att20 where onkeydown_att s = Onkeydown_Att_20 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_20 instance A_Onkeydown Att19 where onkeydown_att s = Onkeydown_Att_19 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_19 instance A_Onkeydown Att18 where onkeydown_att s = Onkeydown_Att_18 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_18 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 Att10 where onkeydown_att s = Onkeydown_Att_10 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_10 instance A_Onkeydown Att6 where onkeydown_att s = Onkeydown_Att_6 (s2b_escape s) onkeydown_att_bs = Onkeydown_Att_6 class A_Target a where target_att :: String -> a target_att_bs :: B.ByteString -> a instance A_Target Att43 where target_att s = Target_Att_43 (s2b_escape s) target_att_bs = Target_Att_43 instance A_Target Att42 where target_att s = Target_Att_42 (s2b_escape s) target_att_bs = Target_Att_42 instance A_Target Att24 where target_att s = Target_Att_24 (s2b_escape s) target_att_bs = Target_Att_24 instance A_Target Att6 where target_att s = Target_Att_6 (s2b_escape s) target_att_bs = Target_Att_6 instance A_Target Att3 where target_att s = Target_Att_3 (s2b_escape s) target_att_bs = Target_Att_3 class A_Onkeyup a where onkeyup_att :: String -> a onkeyup_att_bs :: B.ByteString -> a instance A_Onkeyup Att61 where onkeyup_att s = Onkeyup_Att_61 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_61 instance A_Onkeyup Att60 where onkeyup_att s = Onkeyup_Att_60 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_60 instance A_Onkeyup Att59 where onkeyup_att s = Onkeyup_Att_59 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_59 instance A_Onkeyup Att58 where onkeyup_att s = Onkeyup_Att_58 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_58 instance A_Onkeyup Att57 where onkeyup_att s = Onkeyup_Att_57 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_57 instance A_Onkeyup Att55 where onkeyup_att s = Onkeyup_Att_55 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_55 instance A_Onkeyup Att54 where onkeyup_att s = Onkeyup_Att_54 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_54 instance A_Onkeyup Att51 where onkeyup_att s = Onkeyup_Att_51 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_51 instance A_Onkeyup Att50 where onkeyup_att s = Onkeyup_Att_50 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_50 instance A_Onkeyup Att48 where onkeyup_att s = Onkeyup_Att_48 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_48 instance A_Onkeyup Att47 where onkeyup_att s = Onkeyup_Att_47 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_47 instance A_Onkeyup Att46 where onkeyup_att s = Onkeyup_Att_46 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_46 instance A_Onkeyup Att45 where onkeyup_att s = Onkeyup_Att_45 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_45 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 Att40 where onkeyup_att s = Onkeyup_Att_40 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_40 instance A_Onkeyup Att37 where onkeyup_att s = Onkeyup_Att_37 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_37 instance A_Onkeyup Att31 where onkeyup_att s = Onkeyup_Att_31 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_31 instance A_Onkeyup Att25 where onkeyup_att s = Onkeyup_Att_25 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_25 instance A_Onkeyup Att24 where onkeyup_att s = Onkeyup_Att_24 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_24 instance A_Onkeyup Att23 where onkeyup_att s = Onkeyup_Att_23 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_23 instance A_Onkeyup Att22 where onkeyup_att s = Onkeyup_Att_22 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_22 instance A_Onkeyup Att21 where onkeyup_att s = Onkeyup_Att_21 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_21 instance A_Onkeyup Att20 where onkeyup_att s = Onkeyup_Att_20 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_20 instance A_Onkeyup Att19 where onkeyup_att s = Onkeyup_Att_19 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_19 instance A_Onkeyup Att18 where onkeyup_att s = Onkeyup_Att_18 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_18 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 Att10 where onkeyup_att s = Onkeyup_Att_10 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_10 instance A_Onkeyup Att6 where onkeyup_att s = Onkeyup_Att_6 (s2b_escape s) onkeyup_att_bs = Onkeyup_Att_6 class A_Onreset a where onreset_att :: String -> a onreset_att_bs :: B.ByteString -> a instance A_Onreset Att43 where onreset_att s = Onreset_Att_43 (s2b_escape s) onreset_att_bs = Onreset_Att_43 class A_Code a where code_att :: String -> a code_att_bs :: B.ByteString -> a instance A_Code Att34 where code_att s = Code_Att_34 (s2b_escape s) code_att_bs = Code_Att_34 class A_Valign a where valign_att :: ValignEnum -> a instance A_Valign Att61 where valign_att s = Valign_Att_61 (s2b (show s)) instance A_Valign Att60 where valign_att s = Valign_Att_60 (s2b (show s)) instance A_Valign Att59 where valign_att s = Valign_Att_59 (s2b (show s)) instance A_Valign Att58 where valign_att s = Valign_Att_58 (s2b (show s)) class A_Name a where name_att :: String -> a name_att_bs :: B.ByteString -> a instance A_Name Att55 where name_att s = Name_Att_55 (s2b_escape s) name_att_bs = Name_Att_55 instance A_Name Att51 where name_att s = Name_Att_51 (s2b_escape s) name_att_bs = Name_Att_51 instance A_Name Att47 where name_att s = Name_Att_47 (s2b_escape s) name_att_bs = Name_Att_47 instance A_Name Att46 where name_att s = Name_Att_46 (s2b_escape s) name_att_bs = Name_Att_46 instance A_Name Att43 where name_att s = Name_Att_43 (s2b_escape s) name_att_bs = Name_Att_43 instance A_Name Att40 where name_att s = Name_Att_40 (s2b_escape s) name_att_bs = Name_Att_40 instance A_Name Att37 where name_att s = Name_Att_37 (s2b_escape s) name_att_bs = Name_Att_37 instance A_Name Att34 where name_att s = Name_Att_34 (s2b_escape s) name_att_bs = Name_Att_34 instance A_Name Att33 where name_att s = Name_Att_33 (s2b_escape s) name_att_bs = Name_Att_33 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 Att24 where name_att s = Name_Att_24 (s2b_escape s) name_att_bs = Name_Att_24 instance A_Name Att13 where name_att s = Name_Att_13 (s2b_escape s) name_att_bs = Name_Att_13 instance A_Name Att12 where name_att s = Name_Att_12 (s2b_escape s) name_att_bs = Name_Att_12 instance A_Name Att4 where name_att s = Name_Att_4 (s2b_escape s) name_att_bs = Name_Att_4 class A_Charset a where charset_att :: String -> a charset_att_bs :: B.ByteString -> a instance A_Charset Att24 where charset_att s = Charset_Att_24 (s2b_escape s) charset_att_bs = Charset_Att_24 instance A_Charset Att9 where charset_att s = Charset_Att_9 (s2b_escape s) charset_att_bs = Charset_Att_9 instance A_Charset Att6 where charset_att s = Charset_Att_6 (s2b_escape s) charset_att_bs = Charset_Att_6 class A_Prompt a where prompt_att :: String -> a prompt_att_bs :: B.ByteString -> a instance A_Prompt Att56 where prompt_att s = Prompt_Att_56 (s2b_escape s) prompt_att_bs = Prompt_Att_56 class A_Accept_charset a where accept_charset_att :: String -> a accept_charset_att_bs :: B.ByteString -> a instance A_Accept_charset Att43 where accept_charset_att s = Accept_charset_Att_43 (s2b_escape s) accept_charset_att_bs = Accept_charset_Att_43 class A_Rev a where rev_att :: String -> a rev_att_bs :: B.ByteString -> a instance A_Rev Att24 where rev_att s = Rev_Att_24 (s2b_escape s) rev_att_bs = Rev_Att_24 instance A_Rev Att6 where rev_att s = Rev_Att_6 (s2b_escape s) rev_att_bs = Rev_Att_6 class A_Title a where title_att :: String -> a title_att_bs :: B.ByteString -> a instance A_Title Att61 where title_att s = Title_Att_61 (s2b_escape s) title_att_bs = Title_Att_61 instance A_Title Att60 where title_att s = Title_Att_60 (s2b_escape s) title_att_bs = Title_Att_60 instance A_Title Att59 where title_att s = Title_Att_59 (s2b_escape s) title_att_bs = Title_Att_59 instance A_Title Att58 where title_att s = Title_Att_58 (s2b_escape s) title_att_bs = Title_Att_58 instance A_Title Att57 where title_att s = Title_Att_57 (s2b_escape s) title_att_bs = Title_Att_57 instance A_Title Att56 where title_att s = Title_Att_56 (s2b_escape s) title_att_bs = Title_Att_56 instance A_Title Att55 where title_att s = Title_Att_55 (s2b_escape s) title_att_bs = Title_Att_55 instance A_Title Att54 where title_att s = Title_Att_54 (s2b_escape s) title_att_bs = Title_Att_54 instance A_Title Att51 where title_att s = Title_Att_51 (s2b_escape s) title_att_bs = Title_Att_51 instance A_Title Att50 where title_att s = Title_Att_50 (s2b_escape s) title_att_bs = Title_Att_50 instance A_Title Att48 where title_att s = Title_Att_48 (s2b_escape s) title_att_bs = Title_Att_48 instance A_Title Att47 where title_att s = Title_Att_47 (s2b_escape s) title_att_bs = Title_Att_47 instance A_Title Att46 where title_att s = Title_Att_46 (s2b_escape s) title_att_bs = Title_Att_46 instance A_Title Att45 where title_att s = Title_Att_45 (s2b_escape s) title_att_bs = Title_Att_45 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 Att40 where title_att s = Title_Att_40 (s2b_escape s) title_att_bs = Title_Att_40 instance A_Title Att37 where title_att s = Title_Att_37 (s2b_escape s) title_att_bs = Title_Att_37 instance A_Title Att34 where title_att s = Title_Att_34 (s2b_escape s) title_att_bs = Title_Att_34 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 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 Att24 where title_att s = Title_Att_24 (s2b_escape s) title_att_bs = Title_Att_24 instance A_Title Att23 where title_att s = Title_Att_23 (s2b_escape s) title_att_bs = Title_Att_23 instance A_Title Att22 where title_att s = Title_Att_22 (s2b_escape s) title_att_bs = Title_Att_22 instance A_Title Att21 where title_att s = Title_Att_21 (s2b_escape s) title_att_bs = Title_Att_21 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 Att18 where title_att s = Title_Att_18 (s2b_escape s) title_att_bs = Title_Att_18 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 Att10 where title_att s = Title_Att_10 (s2b_escape s) title_att_bs = Title_Att_10 instance A_Title Att7 where title_att s = Title_Att_7 (s2b_escape s) title_att_bs = Title_Att_7 instance A_Title Att6 where title_att s = Title_Att_6 (s2b_escape s) title_att_bs = Title_Att_6 class A_Start a where start_att :: String -> a start_att_bs :: B.ByteString -> a instance A_Start Att17 where start_att s = Start_Att_17 (s2b_escape s) start_att_bs = Start_Att_17 class A_Enctype a where enctype_att :: String -> a enctype_att_bs :: B.ByteString -> a instance A_Enctype Att43 where enctype_att s = Enctype_Att_43 (s2b_escape s) enctype_att_bs = Enctype_Att_43 class A_Usemap a where usemap_att :: String -> a usemap_att_bs :: B.ByteString -> a instance A_Usemap Att46 where usemap_att s = Usemap_Att_46 (s2b_escape s) usemap_att_bs = Usemap_Att_46 instance A_Usemap Att37 where usemap_att s = Usemap_Att_37 (s2b_escape s) usemap_att_bs = Usemap_Att_37 instance A_Usemap Att31 where usemap_att s = Usemap_Att_31 (s2b_escape s) usemap_att_bs = Usemap_Att_31 class A_Nowrap a where nowrap_att :: String -> a instance A_Nowrap Att61 where nowrap_att s = Nowrap_Att_61 (s2b (show s)) class A_Coords a where coords_att :: String -> a coords_att_bs :: B.ByteString -> a instance A_Coords Att42 where coords_att s = Coords_Att_42 (s2b_escape s) coords_att_bs = Coords_Att_42 instance A_Coords Att24 where coords_att s = Coords_Att_24 (s2b_escape s) coords_att_bs = Coords_Att_24 class A_Onblur a where onblur_att :: String -> a onblur_att_bs :: B.ByteString -> a instance A_Onblur Att55 where onblur_att s = Onblur_Att_55 (s2b_escape s) onblur_att_bs = Onblur_Att_55 instance A_Onblur Att51 where onblur_att s = Onblur_Att_51 (s2b_escape s) onblur_att_bs = Onblur_Att_51 instance A_Onblur Att47 where onblur_att s = Onblur_Att_47 (s2b_escape s) onblur_att_bs = Onblur_Att_47 instance A_Onblur Att46 where onblur_att s = Onblur_Att_46 (s2b_escape s) onblur_att_bs = Onblur_Att_46 instance A_Onblur Att45 where onblur_att s = Onblur_Att_45 (s2b_escape s) onblur_att_bs = Onblur_Att_45 instance A_Onblur Att42 where onblur_att s = Onblur_Att_42 (s2b_escape s) onblur_att_bs = Onblur_Att_42 instance A_Onblur Att24 where onblur_att s = Onblur_Att_24 (s2b_escape s) onblur_att_bs = Onblur_Att_24 class A_Datetime a where datetime_att :: String -> a datetime_att_bs :: B.ByteString -> a instance A_Datetime Att23 where datetime_att s = Datetime_Att_23 (s2b_escape s) datetime_att_bs = Datetime_Att_23 class A_Dir a where dir_att :: DirEnum -> a instance A_Dir Att61 where dir_att s = Dir_Att_61 (s2b (show s)) instance A_Dir Att60 where dir_att s = Dir_Att_60 (s2b (show s)) instance A_Dir Att59 where dir_att s = Dir_Att_59 (s2b (show s)) instance A_Dir Att58 where dir_att s = Dir_Att_58 (s2b (show s)) instance A_Dir Att57 where dir_att s = Dir_Att_57 (s2b (show s)) instance A_Dir Att56 where dir_att s = Dir_Att_56 (s2b (show s)) instance A_Dir Att55 where dir_att s = Dir_Att_55 (s2b (show s)) instance A_Dir Att54 where dir_att s = Dir_Att_54 (s2b (show s)) instance A_Dir Att51 where dir_att s = Dir_Att_51 (s2b (show s)) instance A_Dir Att50 where dir_att s = Dir_Att_50 (s2b (show s)) instance A_Dir Att48 where dir_att s = Dir_Att_48 (s2b (show s)) instance A_Dir Att47 where dir_att s = Dir_Att_47 (s2b (show s)) instance A_Dir Att46 where dir_att s = Dir_Att_46 (s2b (show s)) instance A_Dir Att45 where dir_att s = Dir_Att_45 (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 Att40 where dir_att s = Dir_Att_40 (s2b (show s)) instance A_Dir Att37 where dir_att s = Dir_Att_37 (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 Att26 where dir_att s = Dir_Att_26 (s2b (show s)) instance A_Dir Att25 where dir_att s = Dir_Att_25 (s2b (show s)) instance A_Dir Att24 where dir_att s = Dir_Att_24 (s2b (show s)) instance A_Dir Att23 where dir_att s = Dir_Att_23 (s2b (show s)) instance A_Dir Att22 where dir_att s = Dir_Att_22 (s2b (show s)) instance A_Dir Att21 where dir_att s = Dir_Att_21 (s2b (show s)) instance A_Dir Att20 where dir_att s = Dir_Att_20 (s2b (show s)) instance A_Dir Att19 where dir_att s = Dir_Att_19 (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 Att10 where dir_att s = Dir_Att_10 (s2b (show s)) instance A_Dir Att7 where dir_att s = Dir_Att_7 (s2b (show s)) instance A_Dir Att6 where dir_att s = Dir_Att_6 (s2b (show s)) instance A_Dir Att4 where dir_att s = Dir_Att_4 (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_Color a where color_att :: String -> a color_att_bs :: B.ByteString -> a instance A_Color Att30 where color_att s = Color_Att_30 (s2b_escape s) color_att_bs = Color_Att_30 instance A_Color Att28 where color_att s = Color_Att_28 (s2b_escape s) color_att_bs = Color_Att_28 class A_Vspace a where vspace_att :: String -> a vspace_att_bs :: B.ByteString -> a instance A_Vspace Att37 where vspace_att s = Vspace_Att_37 (s2b_escape s) vspace_att_bs = Vspace_Att_37 instance A_Vspace Att34 where vspace_att s = Vspace_Att_34 (s2b_escape s) vspace_att_bs = Vspace_Att_34 instance A_Vspace Att31 where vspace_att s = Vspace_Att_31 (s2b_escape s) vspace_att_bs = Vspace_Att_31 class A_Background a where background_att :: String -> a background_att_bs :: B.ByteString -> a instance A_Background Att14 where background_att s = Background_Att_14 (s2b_escape s) background_att_bs = Background_Att_14 class A_Height a where height_att :: String -> a height_att_bs :: B.ByteString -> a instance A_Height Att61 where height_att s = Height_Att_61 (s2b_escape s) height_att_bs = Height_Att_61 instance A_Height Att37 where height_att s = Height_Att_37 (s2b_escape s) height_att_bs = Height_Att_37 instance A_Height Att36 where height_att s = Height_Att_36 (s2b_escape s) height_att_bs = Height_Att_36 instance A_Height Att34 where height_att s = Height_Att_34 (s2b_escape s) height_att_bs = Height_Att_34 instance A_Height Att31 where height_att s = Height_Att_31 (s2b_escape s) height_att_bs = Height_Att_31 instance A_Height Att13 where height_att s = Height_Att_13 (s2b_escape s) height_att_bs = Height_Att_13 class A_Char a where char_att :: String -> a char_att_bs :: B.ByteString -> a instance A_Char Att61 where char_att s = Char_Att_61 (s2b_escape s) char_att_bs = Char_Att_61 instance A_Char Att60 where char_att s = Char_Att_60 (s2b_escape s) char_att_bs = Char_Att_60 instance A_Char Att59 where char_att s = Char_Att_59 (s2b_escape s) char_att_bs = Char_Att_59 instance A_Char Att58 where char_att s = Char_Att_58 (s2b_escape s) char_att_bs = Char_Att_58 class A_Codebase a where codebase_att :: String -> a codebase_att_bs :: B.ByteString -> a instance A_Codebase Att34 where codebase_att s = Codebase_Att_34 (s2b_escape s) codebase_att_bs = Codebase_Att_34 instance A_Codebase Att31 where codebase_att s = Codebase_Att_31 (s2b_escape s) codebase_att_bs = Codebase_Att_31 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 Att24 where rel_att s = Rel_Att_24 (s2b_escape s) rel_att_bs = Rel_Att_24 instance A_Rel Att6 where rel_att s = Rel_Att_6 (s2b_escape s) rel_att_bs = Rel_Att_6 class A_Onsubmit a where onsubmit_att :: String -> a onsubmit_att_bs :: B.ByteString -> a instance A_Onsubmit Att43 where onsubmit_att s = Onsubmit_Att_43 (s2b_escape s) onsubmit_att_bs = Onsubmit_Att_43 class A_Marginwidth a where marginwidth_att :: String -> a marginwidth_att_bs :: B.ByteString -> a instance A_Marginwidth Att13 where marginwidth_att s = Marginwidth_Att_13 (s2b_escape s) marginwidth_att_bs = Marginwidth_Att_13 instance A_Marginwidth Att12 where marginwidth_att s = Marginwidth_Att_12 (s2b_escape s) marginwidth_att_bs = Marginwidth_Att_12 class A_Abbr a where abbr_att :: String -> a abbr_att_bs :: B.ByteString -> a instance A_Abbr Att61 where abbr_att s = Abbr_Att_61 (s2b_escape s) abbr_att_bs = Abbr_Att_61 class A_Onchange a where onchange_att :: String -> a onchange_att_bs :: B.ByteString -> a instance A_Onchange Att51 where onchange_att s = Onchange_Att_51 (s2b_escape s) onchange_att_bs = Onchange_Att_51 instance A_Onchange Att47 where onchange_att s = Onchange_Att_47 (s2b_escape s) onchange_att_bs = Onchange_Att_47 instance A_Onchange Att46 where onchange_att s = Onchange_Att_46 (s2b_escape s) onchange_att_bs = Onchange_Att_46 class A_Href a where href_att :: String -> a href_att_bs :: B.ByteString -> a instance A_Href Att42 where href_att s = Href_Att_42 (s2b_escape s) href_att_bs = Href_Att_42 instance A_Href Att24 where href_att s = Href_Att_24 (s2b_escape s) href_att_bs = Href_Att_24 instance A_Href Att6 where href_att s = Href_Att_6 (s2b_escape s) href_att_bs = Href_Att_6 instance A_Href Att3 where href_att s = Href_Att_3 (s2b_escape s) href_att_bs = Href_Att_3 class A_Id a where id_att :: String -> a id_att_bs :: B.ByteString -> a instance A_Id Att61 where id_att s = Id_Att_61 (s2b_escape s) id_att_bs = Id_Att_61 instance A_Id Att60 where id_att s = Id_Att_60 (s2b_escape s) id_att_bs = Id_Att_60 instance A_Id Att59 where id_att s = Id_Att_59 (s2b_escape s) id_att_bs = Id_Att_59 instance A_Id Att58 where id_att s = Id_Att_58 (s2b_escape s) id_att_bs = Id_Att_58 instance A_Id Att57 where id_att s = Id_Att_57 (s2b_escape s) id_att_bs = Id_Att_57 instance A_Id Att56 where id_att s = Id_Att_56 (s2b_escape s) id_att_bs = Id_Att_56 instance A_Id Att55 where id_att s = Id_Att_55 (s2b_escape s) id_att_bs = Id_Att_55 instance A_Id Att54 where id_att s = Id_Att_54 (s2b_escape s) id_att_bs = Id_Att_54 instance A_Id Att51 where id_att s = Id_Att_51 (s2b_escape s) id_att_bs = Id_Att_51 instance A_Id Att50 where id_att s = Id_Att_50 (s2b_escape s) id_att_bs = Id_Att_50 instance A_Id Att48 where id_att s = Id_Att_48 (s2b_escape s) id_att_bs = Id_Att_48 instance A_Id Att47 where id_att s = Id_Att_47 (s2b_escape s) id_att_bs = Id_Att_47 instance A_Id Att46 where id_att s = Id_Att_46 (s2b_escape s) id_att_bs = Id_Att_46 instance A_Id Att45 where id_att s = Id_Att_45 (s2b_escape s) id_att_bs = Id_Att_45 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 Att37 where id_att s = Id_Att_37 (s2b_escape s) id_att_bs = Id_Att_37 instance A_Id Att34 where id_att s = Id_Att_34 (s2b_escape s) id_att_bs = Id_Att_34 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 Att25 where id_att s = Id_Att_25 (s2b_escape s) id_att_bs = Id_Att_25 instance A_Id Att24 where id_att s = Id_Att_24 (s2b_escape s) id_att_bs = Id_Att_24 instance A_Id Att23 where id_att s = Id_Att_23 (s2b_escape s) id_att_bs = Id_Att_23 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 Att18 where id_att s = Id_Att_18 (s2b_escape s) id_att_bs = Id_Att_18 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 Att9 where id_att s = Id_Att_9 (s2b_escape s) id_att_bs = Id_Att_9 instance A_Id Att7 where id_att s = Id_Att_7 (s2b_escape s) id_att_bs = Id_Att_7 instance A_Id Att6 where id_att s = Id_Att_6 (s2b_escape s) id_att_bs = Id_Att_6 instance A_Id Att4 where id_att s = Id_Att_4 (s2b_escape s) id_att_bs = Id_Att_4 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_Value a where value_att :: String -> a value_att_bs :: B.ByteString -> a instance A_Value Att55 where value_att s = Value_Att_55 (s2b_escape s) value_att_bs = Value_Att_55 instance A_Value Att50 where value_att s = Value_Att_50 (s2b_escape s) value_att_bs = Value_Att_50 instance A_Value Att46 where value_att s = Value_Att_46 (s2b_escape s) value_att_bs = Value_Att_46 instance A_Value Att32 where value_att s = Value_Att_32 (s2b_escape s) value_att_bs = Value_Att_32 instance A_Value Att19 where value_att s = Value_Att_19 (s2b_escape s) value_att_bs = Value_Att_19 class A_Data a where data_att :: String -> a data_att_bs :: B.ByteString -> a instance A_Data Att31 where data_att s = Data_Att_31 (s2b_escape s) data_att_bs = Data_Att_31 class A_Declare a where declare_att :: String -> a instance A_Declare Att31 where declare_att s = Declare_Att_31 (s2b (show s)) class A_Type a where type_att :: String -> a type_att_bs :: B.ByteString -> a instance A_Type Att55 where type_att s = Type_Att_55 (s2b_escape s) type_att_bs = Type_Att_55 instance A_Type Att46 where type_att s = Type_Att_46 (s2b_escape s) type_att_bs = Type_Att_46 instance A_Type Att32 where type_att s = Type_Att_32 (s2b_escape s) type_att_bs = Type_Att_32 instance A_Type Att31 where type_att s = Type_Att_31 (s2b_escape s) type_att_bs = Type_Att_31 instance A_Type Att24 where type_att s = Type_Att_24 (s2b_escape s) type_att_bs = Type_Att_24 instance A_Type Att19 where type_att s = Type_Att_19 (s2b_escape s) type_att_bs = Type_Att_19 instance A_Type Att17 where type_att s = Type_Att_17 (s2b_escape s) type_att_bs = Type_Att_17 instance A_Type Att16 where type_att s = Type_Att_16 (s2b_escape s) type_att_bs = Type_Att_16 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 instance A_Type Att6 where type_att s = Type_Att_6 (s2b_escape s) type_att_bs = Type_Att_6 class A_Headers a where headers_att :: String -> a headers_att_bs :: B.ByteString -> a instance A_Headers Att61 where headers_att s = Headers_Att_61 (s2b_escape s) headers_att_bs = Headers_Att_61 class A_Object a where object_att :: String -> a object_att_bs :: B.ByteString -> a instance A_Object Att34 where object_att s = Object_Att_34 (s2b_escape s) object_att_bs = Object_Att_34 class A_Noresize a where noresize_att :: String -> a instance A_Noresize Att12 where noresize_att s = Noresize_Att_12 (s2b (show s)) class A_Rowspan a where rowspan_att :: String -> a rowspan_att_bs :: B.ByteString -> a instance A_Rowspan Att61 where rowspan_att s = Rowspan_Att_61 (s2b_escape s) rowspan_att_bs = Rowspan_Att_61 class A_Defer a where defer_att :: String -> a instance A_Defer Att9 where defer_att s = Defer_Att_9 (s2b (show s)) class A_Cellspacing a where cellspacing_att :: String -> a cellspacing_att_bs :: B.ByteString -> a instance A_Cellspacing Att57 where cellspacing_att s = Cellspacing_Att_57 (s2b_escape s) cellspacing_att_bs = Cellspacing_Att_57 class A_Charoff a where charoff_att :: String -> a charoff_att_bs :: B.ByteString -> a instance A_Charoff Att61 where charoff_att s = Charoff_Att_61 (s2b_escape s) charoff_att_bs = Charoff_Att_61 instance A_Charoff Att60 where charoff_att s = Charoff_Att_60 (s2b_escape s) charoff_att_bs = Charoff_Att_60 instance A_Charoff Att59 where charoff_att s = Charoff_Att_59 (s2b_escape s) charoff_att_bs = Charoff_Att_59 instance A_Charoff Att58 where charoff_att s = Charoff_Att_58 (s2b_escape s) charoff_att_bs = Charoff_Att_58 class A_Accept a where accept_att :: String -> a accept_att_bs :: B.ByteString -> a instance A_Accept Att46 where accept_att s = Accept_Att_46 (s2b_escape s) accept_att_bs = Accept_Att_46 instance A_Accept Att43 where accept_att s = Accept_Att_43 (s2b_escape s) accept_att_bs = Accept_Att_43 class A_Alt a where alt_att :: String -> a alt_att_bs :: B.ByteString -> a instance A_Alt Att46 where alt_att s = Alt_Att_46 (s2b_escape s) alt_att_bs = Alt_Att_46 instance A_Alt Att42 where alt_att s = Alt_Att_42 (s2b_escape s) alt_att_bs = Alt_Att_42 instance A_Alt Att39 where alt_att s = Alt_Att_39 (s2b_escape s) alt_att_bs = Alt_Att_39 instance A_Alt Att37 where alt_att s = Alt_Att_37 (s2b_escape s) alt_att_bs = Alt_Att_37 instance A_Alt Att34 where alt_att s = Alt_Att_34 (s2b_escape s) alt_att_bs = Alt_Att_34 class A_Onmouseout a where onmouseout_att :: String -> a onmouseout_att_bs :: B.ByteString -> a instance A_Onmouseout Att61 where onmouseout_att s = Onmouseout_Att_61 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_61 instance A_Onmouseout Att60 where onmouseout_att s = Onmouseout_Att_60 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_60 instance A_Onmouseout Att59 where onmouseout_att s = Onmouseout_Att_59 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_59 instance A_Onmouseout Att58 where onmouseout_att s = Onmouseout_Att_58 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_58 instance A_Onmouseout Att57 where onmouseout_att s = Onmouseout_Att_57 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_57 instance A_Onmouseout Att55 where onmouseout_att s = Onmouseout_Att_55 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_55 instance A_Onmouseout Att54 where onmouseout_att s = Onmouseout_Att_54 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_54 instance A_Onmouseout Att51 where onmouseout_att s = Onmouseout_Att_51 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_51 instance A_Onmouseout Att50 where onmouseout_att s = Onmouseout_Att_50 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_50 instance A_Onmouseout Att48 where onmouseout_att s = Onmouseout_Att_48 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_48 instance A_Onmouseout Att47 where onmouseout_att s = Onmouseout_Att_47 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_47 instance A_Onmouseout Att46 where onmouseout_att s = Onmouseout_Att_46 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_46 instance A_Onmouseout Att45 where onmouseout_att s = Onmouseout_Att_45 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_45 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 Att40 where onmouseout_att s = Onmouseout_Att_40 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_40 instance A_Onmouseout Att37 where onmouseout_att s = Onmouseout_Att_37 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_37 instance A_Onmouseout Att31 where onmouseout_att s = Onmouseout_Att_31 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_31 instance A_Onmouseout Att25 where onmouseout_att s = Onmouseout_Att_25 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_25 instance A_Onmouseout Att24 where onmouseout_att s = Onmouseout_Att_24 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_24 instance A_Onmouseout Att23 where onmouseout_att s = Onmouseout_Att_23 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_23 instance A_Onmouseout Att22 where onmouseout_att s = Onmouseout_Att_22 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_22 instance A_Onmouseout Att21 where onmouseout_att s = Onmouseout_Att_21 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_21 instance A_Onmouseout Att20 where onmouseout_att s = Onmouseout_Att_20 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_20 instance A_Onmouseout Att19 where onmouseout_att s = Onmouseout_Att_19 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_19 instance A_Onmouseout Att18 where onmouseout_att s = Onmouseout_Att_18 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_18 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 Att10 where onmouseout_att s = Onmouseout_Att_10 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_10 instance A_Onmouseout Att6 where onmouseout_att s = Onmouseout_Att_6 (s2b_escape s) onmouseout_att_bs = Onmouseout_Att_6 class A_Border a where border_att :: String -> a border_att_bs :: B.ByteString -> a instance A_Border Att57 where border_att s = Border_Att_57 (s2b_escape s) border_att_bs = Border_Att_57 instance A_Border Att37 where border_att s = Border_Att_37 (s2b_escape s) border_att_bs = Border_Att_37 instance A_Border Att31 where border_att s = Border_Att_31 (s2b_escape s) border_att_bs = Border_Att_31 class A_Onunload a where onunload_att :: String -> a onunload_att_bs :: B.ByteString -> a instance A_Onunload Att14 where onunload_att s = Onunload_Att_14 (s2b_escape s) onunload_att_bs = Onunload_Att_14 instance A_Onunload Att11 where onunload_att s = Onunload_Att_11 (s2b_escape s) onunload_att_bs = Onunload_Att_11 class A_Cellpadding a where cellpadding_att :: String -> a cellpadding_att_bs :: B.ByteString -> a instance A_Cellpadding Att57 where cellpadding_att s = Cellpadding_Att_57 (s2b_escape s) cellpadding_att_bs = Cellpadding_Att_57 class A_Valuetype a where valuetype_att :: ValuetypeEnum -> a instance A_Valuetype Att32 where valuetype_att s = Valuetype_Att_32 (s2b (show s)) class A_Content a where content_att :: String -> a content_att_bs :: B.ByteString -> a instance A_Content Att5 where content_att s = Content_Att_5 (s2b_escape s) content_att_bs = Content_Att_5 instance A_Content Att4 where content_att s = Content_Att_4 (s2b_escape s) content_att_bs = Content_Att_4 class A_Clear a where clear_att :: ClearEnum -> a instance A_Clear Att27 where clear_att s = Clear_Att_27 (s2b (show s)) class A_Onmouseup a where onmouseup_att :: String -> a onmouseup_att_bs :: B.ByteString -> a instance A_Onmouseup Att61 where onmouseup_att s = Onmouseup_Att_61 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_61 instance A_Onmouseup Att60 where onmouseup_att s = Onmouseup_Att_60 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_60 instance A_Onmouseup Att59 where onmouseup_att s = Onmouseup_Att_59 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_59 instance A_Onmouseup Att58 where onmouseup_att s = Onmouseup_Att_58 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_58 instance A_Onmouseup Att57 where onmouseup_att s = Onmouseup_Att_57 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_57 instance A_Onmouseup Att55 where onmouseup_att s = Onmouseup_Att_55 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_55 instance A_Onmouseup Att54 where onmouseup_att s = Onmouseup_Att_54 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_54 instance A_Onmouseup Att51 where onmouseup_att s = Onmouseup_Att_51 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_51 instance A_Onmouseup Att50 where onmouseup_att s = Onmouseup_Att_50 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_50 instance A_Onmouseup Att48 where onmouseup_att s = Onmouseup_Att_48 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_48 instance A_Onmouseup Att47 where onmouseup_att s = Onmouseup_Att_47 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_47 instance A_Onmouseup Att46 where onmouseup_att s = Onmouseup_Att_46 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_46 instance A_Onmouseup Att45 where onmouseup_att s = Onmouseup_Att_45 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_45 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 Att40 where onmouseup_att s = Onmouseup_Att_40 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_40 instance A_Onmouseup Att37 where onmouseup_att s = Onmouseup_Att_37 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_37 instance A_Onmouseup Att31 where onmouseup_att s = Onmouseup_Att_31 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_31 instance A_Onmouseup Att25 where onmouseup_att s = Onmouseup_Att_25 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_25 instance A_Onmouseup Att24 where onmouseup_att s = Onmouseup_Att_24 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_24 instance A_Onmouseup Att23 where onmouseup_att s = Onmouseup_Att_23 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_23 instance A_Onmouseup Att22 where onmouseup_att s = Onmouseup_Att_22 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_22 instance A_Onmouseup Att21 where onmouseup_att s = Onmouseup_Att_21 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_21 instance A_Onmouseup Att20 where onmouseup_att s = Onmouseup_Att_20 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_20 instance A_Onmouseup Att19 where onmouseup_att s = Onmouseup_Att_19 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_19 instance A_Onmouseup Att18 where onmouseup_att s = Onmouseup_Att_18 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_18 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 Att10 where onmouseup_att s = Onmouseup_Att_10 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_10 instance A_Onmouseup Att6 where onmouseup_att s = Onmouseup_Att_6 (s2b_escape s) onmouseup_att_bs = Onmouseup_Att_6 class A_Scope a where scope_att :: ScopeEnum -> a instance A_Scope Att61 where scope_att s = Scope_Att_61 (s2b (show s)) class A_Onmouseover a where onmouseover_att :: String -> a onmouseover_att_bs :: B.ByteString -> a instance A_Onmouseover Att61 where onmouseover_att s = Onmouseover_Att_61 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_61 instance A_Onmouseover Att60 where onmouseover_att s = Onmouseover_Att_60 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_60 instance A_Onmouseover Att59 where onmouseover_att s = Onmouseover_Att_59 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_59 instance A_Onmouseover Att58 where onmouseover_att s = Onmouseover_Att_58 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_58 instance A_Onmouseover Att57 where onmouseover_att s = Onmouseover_Att_57 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_57 instance A_Onmouseover Att55 where onmouseover_att s = Onmouseover_Att_55 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_55 instance A_Onmouseover Att54 where onmouseover_att s = Onmouseover_Att_54 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_54 instance A_Onmouseover Att51 where onmouseover_att s = Onmouseover_Att_51 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_51 instance A_Onmouseover Att50 where onmouseover_att s = Onmouseover_Att_50 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_50 instance A_Onmouseover Att48 where onmouseover_att s = Onmouseover_Att_48 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_48 instance A_Onmouseover Att47 where onmouseover_att s = Onmouseover_Att_47 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_47 instance A_Onmouseover Att46 where onmouseover_att s = Onmouseover_Att_46 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_46 instance A_Onmouseover Att45 where onmouseover_att s = Onmouseover_Att_45 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_45 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 Att40 where onmouseover_att s = Onmouseover_Att_40 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_40 instance A_Onmouseover Att37 where onmouseover_att s = Onmouseover_Att_37 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_37 instance A_Onmouseover Att31 where onmouseover_att s = Onmouseover_Att_31 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_31 instance A_Onmouseover Att25 where onmouseover_att s = Onmouseover_Att_25 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_25 instance A_Onmouseover Att24 where onmouseover_att s = Onmouseover_Att_24 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_24 instance A_Onmouseover Att23 where onmouseover_att s = Onmouseover_Att_23 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_23 instance A_Onmouseover Att22 where onmouseover_att s = Onmouseover_Att_22 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_22 instance A_Onmouseover Att21 where onmouseover_att s = Onmouseover_Att_21 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_21 instance A_Onmouseover Att20 where onmouseover_att s = Onmouseover_Att_20 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_20 instance A_Onmouseover Att19 where onmouseover_att s = Onmouseover_Att_19 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_19 instance A_Onmouseover Att18 where onmouseover_att s = Onmouseover_Att_18 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_18 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 Att10 where onmouseover_att s = Onmouseover_Att_10 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_10 instance A_Onmouseover Att6 where onmouseover_att s = Onmouseover_Att_6 (s2b_escape s) onmouseover_att_bs = Onmouseover_Att_6 class A_Lang a where lang_att :: String -> a lang_att_bs :: B.ByteString -> a instance A_Lang Att61 where lang_att s = Lang_Att_61 (s2b_escape s) lang_att_bs = Lang_Att_61 instance A_Lang Att60 where lang_att s = Lang_Att_60 (s2b_escape s) lang_att_bs = Lang_Att_60 instance A_Lang Att59 where lang_att s = Lang_Att_59 (s2b_escape s) lang_att_bs = Lang_Att_59 instance A_Lang Att58 where lang_att s = Lang_Att_58 (s2b_escape s) lang_att_bs = Lang_Att_58 instance A_Lang Att57 where lang_att s = Lang_Att_57 (s2b_escape s) lang_att_bs = Lang_Att_57 instance A_Lang Att56 where lang_att s = Lang_Att_56 (s2b_escape s) lang_att_bs = Lang_Att_56 instance A_Lang Att55 where lang_att s = Lang_Att_55 (s2b_escape s) lang_att_bs = Lang_Att_55 instance A_Lang Att54 where lang_att s = Lang_Att_54 (s2b_escape s) lang_att_bs = Lang_Att_54 instance A_Lang Att51 where lang_att s = Lang_Att_51 (s2b_escape s) lang_att_bs = Lang_Att_51 instance A_Lang Att50 where lang_att s = Lang_Att_50 (s2b_escape s) lang_att_bs = Lang_Att_50 instance A_Lang Att48 where lang_att s = Lang_Att_48 (s2b_escape s) lang_att_bs = Lang_Att_48 instance A_Lang Att47 where lang_att s = Lang_Att_47 (s2b_escape s) lang_att_bs = Lang_Att_47 instance A_Lang Att46 where lang_att s = Lang_Att_46 (s2b_escape s) lang_att_bs = Lang_Att_46 instance A_Lang Att45 where lang_att s = Lang_Att_45 (s2b_escape s) lang_att_bs = Lang_Att_45 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 Att40 where lang_att s = Lang_Att_40 (s2b_escape s) lang_att_bs = Lang_Att_40 instance A_Lang Att37 where lang_att s = Lang_Att_37 (s2b_escape s) lang_att_bs = Lang_Att_37 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 Att25 where lang_att s = Lang_Att_25 (s2b_escape s) lang_att_bs = Lang_Att_25 instance A_Lang Att24 where lang_att s = Lang_Att_24 (s2b_escape s) lang_att_bs = Lang_Att_24 instance A_Lang Att23 where lang_att s = Lang_Att_23 (s2b_escape s) lang_att_bs = Lang_Att_23 instance A_Lang Att22 where lang_att s = Lang_Att_22 (s2b_escape s) lang_att_bs = Lang_Att_22 instance A_Lang Att21 where lang_att s = Lang_Att_21 (s2b_escape s) lang_att_bs = Lang_Att_21 instance A_Lang Att20 where lang_att s = Lang_Att_20 (s2b_escape s) lang_att_bs = Lang_Att_20 instance A_Lang Att19 where lang_att s = Lang_Att_19 (s2b_escape s) lang_att_bs = Lang_Att_19 instance A_Lang Att18 where lang_att s = Lang_Att_18 (s2b_escape s) lang_att_bs = Lang_Att_18 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 Att10 where lang_att s = Lang_Att_10 (s2b_escape s) lang_att_bs = Lang_Att_10 instance A_Lang Att7 where lang_att s = Lang_Att_7 (s2b_escape s) lang_att_bs = Lang_Att_7 instance A_Lang Att6 where lang_att s = Lang_Att_6 (s2b_escape s) lang_att_bs = Lang_Att_6 instance A_Lang Att4 where lang_att s = Lang_Att_4 (s2b_escape s) lang_att_bs = Lang_Att_4 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_Align a where align_att :: AlignEnum -> a instance A_Align Att61 where align_att s = Align_Att_61 (s2b (show s)) instance A_Align Att60 where align_att s = Align_Att_60 (s2b (show s)) instance A_Align Att59 where align_att s = Align_Att_59 (s2b (show s)) instance A_Align Att58 where align_att s = Align_Att_58 (s2b (show s)) instance A_Align Att57 where align_att s = Align_Att_57 (s2b (show s)) instance A_Align Att54 where align_att s = Align_Att_54 (s2b (show s)) instance A_Align Att46 where align_att s = Align_Att_46 (s2b (show s)) instance A_Align Att37 where align_att s = Align_Att_37 (s2b (show s)) instance A_Align Att34 where align_att s = Align_Att_34 (s2b (show s)) instance A_Align Att31 where align_att s = Align_Att_31 (s2b (show s)) instance A_Align Att20 where align_att s = Align_Att_20 (s2b (show s)) instance A_Align Att15 where align_att s = Align_Att_15 (s2b (show s)) instance A_Align Att13 where align_att s = Align_Att_13 (s2b (show s)) class A_Scheme a where scheme_att :: String -> a scheme_att_bs :: B.ByteString -> a instance A_Scheme Att4 where scheme_att s = Scheme_Att_4 (s2b_escape s) scheme_att_bs = Scheme_Att_4 class A_Frameborder a where frameborder_att :: FrameborderEnum -> a instance A_Frameborder Att13 where frameborder_att s = Frameborder_Att_13 (s2b (show s)) instance A_Frameborder Att12 where frameborder_att s = Frameborder_Att_12 (s2b (show s)) class A_Onmousedown a where onmousedown_att :: String -> a onmousedown_att_bs :: B.ByteString -> a instance A_Onmousedown Att61 where onmousedown_att s = Onmousedown_Att_61 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_61 instance A_Onmousedown Att60 where onmousedown_att s = Onmousedown_Att_60 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_60 instance A_Onmousedown Att59 where onmousedown_att s = Onmousedown_Att_59 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_59 instance A_Onmousedown Att58 where onmousedown_att s = Onmousedown_Att_58 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_58 instance A_Onmousedown Att57 where onmousedown_att s = Onmousedown_Att_57 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_57 instance A_Onmousedown Att55 where onmousedown_att s = Onmousedown_Att_55 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_55 instance A_Onmousedown Att54 where onmousedown_att s = Onmousedown_Att_54 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_54 instance A_Onmousedown Att51 where onmousedown_att s = Onmousedown_Att_51 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_51 instance A_Onmousedown Att50 where onmousedown_att s = Onmousedown_Att_50 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_50 instance A_Onmousedown Att48 where onmousedown_att s = Onmousedown_Att_48 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_48 instance A_Onmousedown Att47 where onmousedown_att s = Onmousedown_Att_47 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_47 instance A_Onmousedown Att46 where onmousedown_att s = Onmousedown_Att_46 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_46 instance A_Onmousedown Att45 where onmousedown_att s = Onmousedown_Att_45 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_45 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 Att40 where onmousedown_att s = Onmousedown_Att_40 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_40 instance A_Onmousedown Att37 where onmousedown_att s = Onmousedown_Att_37 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_37 instance A_Onmousedown Att31 where onmousedown_att s = Onmousedown_Att_31 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_31 instance A_Onmousedown Att25 where onmousedown_att s = Onmousedown_Att_25 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_25 instance A_Onmousedown Att24 where onmousedown_att s = Onmousedown_Att_24 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_24 instance A_Onmousedown Att23 where onmousedown_att s = Onmousedown_Att_23 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_23 instance A_Onmousedown Att22 where onmousedown_att s = Onmousedown_Att_22 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_22 instance A_Onmousedown Att21 where onmousedown_att s = Onmousedown_Att_21 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_21 instance A_Onmousedown Att20 where onmousedown_att s = Onmousedown_Att_20 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_20 instance A_Onmousedown Att19 where onmousedown_att s = Onmousedown_Att_19 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_19 instance A_Onmousedown Att18 where onmousedown_att s = Onmousedown_Att_18 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_18 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 Att10 where onmousedown_att s = Onmousedown_Att_10 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_10 instance A_Onmousedown Att6 where onmousedown_att s = Onmousedown_Att_6 (s2b_escape s) onmousedown_att_bs = Onmousedown_Att_6 class A_Onclick a where onclick_att :: String -> a onclick_att_bs :: B.ByteString -> a instance A_Onclick Att61 where onclick_att s = Onclick_Att_61 (s2b_escape s) onclick_att_bs = Onclick_Att_61 instance A_Onclick Att60 where onclick_att s = Onclick_Att_60 (s2b_escape s) onclick_att_bs = Onclick_Att_60 instance A_Onclick Att59 where onclick_att s = Onclick_Att_59 (s2b_escape s) onclick_att_bs = Onclick_Att_59 instance A_Onclick Att58 where onclick_att s = Onclick_Att_58 (s2b_escape s) onclick_att_bs = Onclick_Att_58 instance A_Onclick Att57 where onclick_att s = Onclick_Att_57 (s2b_escape s) onclick_att_bs = Onclick_Att_57 instance A_Onclick Att55 where onclick_att s = Onclick_Att_55 (s2b_escape s) onclick_att_bs = Onclick_Att_55 instance A_Onclick Att54 where onclick_att s = Onclick_Att_54 (s2b_escape s) onclick_att_bs = Onclick_Att_54 instance A_Onclick Att51 where onclick_att s = Onclick_Att_51 (s2b_escape s) onclick_att_bs = Onclick_Att_51 instance A_Onclick Att50 where onclick_att s = Onclick_Att_50 (s2b_escape s) onclick_att_bs = Onclick_Att_50 instance A_Onclick Att48 where onclick_att s = Onclick_Att_48 (s2b_escape s) onclick_att_bs = Onclick_Att_48 instance A_Onclick Att47 where onclick_att s = Onclick_Att_47 (s2b_escape s) onclick_att_bs = Onclick_Att_47 instance A_Onclick Att46 where onclick_att s = Onclick_Att_46 (s2b_escape s) onclick_att_bs = Onclick_Att_46 instance A_Onclick Att45 where onclick_att s = Onclick_Att_45 (s2b_escape s) onclick_att_bs = Onclick_Att_45 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 Att40 where onclick_att s = Onclick_Att_40 (s2b_escape s) onclick_att_bs = Onclick_Att_40 instance A_Onclick Att37 where onclick_att s = Onclick_Att_37 (s2b_escape s) onclick_att_bs = Onclick_Att_37 instance A_Onclick Att31 where onclick_att s = Onclick_Att_31 (s2b_escape s) onclick_att_bs = Onclick_Att_31 instance A_Onclick Att25 where onclick_att s = Onclick_Att_25 (s2b_escape s) onclick_att_bs = Onclick_Att_25 instance A_Onclick Att24 where onclick_att s = Onclick_Att_24 (s2b_escape s) onclick_att_bs = Onclick_Att_24 instance A_Onclick Att23 where onclick_att s = Onclick_Att_23 (s2b_escape s) onclick_att_bs = Onclick_Att_23 instance A_Onclick Att22 where onclick_att s = Onclick_Att_22 (s2b_escape s) onclick_att_bs = Onclick_Att_22 instance A_Onclick Att21 where onclick_att s = Onclick_Att_21 (s2b_escape s) onclick_att_bs = Onclick_Att_21 instance A_Onclick Att20 where onclick_att s = Onclick_Att_20 (s2b_escape s) onclick_att_bs = Onclick_Att_20 instance A_Onclick Att19 where onclick_att s = Onclick_Att_19 (s2b_escape s) onclick_att_bs = Onclick_Att_19 instance A_Onclick Att18 where onclick_att s = Onclick_Att_18 (s2b_escape s) onclick_att_bs = Onclick_Att_18 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 Att10 where onclick_att s = Onclick_Att_10 (s2b_escape s) onclick_att_bs = Onclick_Att_10 instance A_Onclick Att6 where onclick_att s = Onclick_Att_6 (s2b_escape s) onclick_att_bs = Onclick_Att_6 class A_Span a where span_att :: String -> a span_att_bs :: B.ByteString -> a instance A_Span Att59 where span_att s = Span_Att_59 (s2b_escape s) span_att_bs = Span_Att_59 class A_Width a where width_att :: String -> a width_att_bs :: B.ByteString -> a instance A_Width Att61 where width_att s = Width_Att_61 (s2b_escape s) width_att_bs = Width_Att_61 instance A_Width Att59 where width_att s = Width_Att_59 (s2b_escape s) width_att_bs = Width_Att_59 instance A_Width Att57 where width_att s = Width_Att_57 (s2b_escape s) width_att_bs = Width_Att_57 instance A_Width Att37 where width_att s = Width_Att_37 (s2b_escape s) width_att_bs = Width_Att_37 instance A_Width Att35 where width_att s = Width_Att_35 (s2b_escape s) width_att_bs = Width_Att_35 instance A_Width Att34 where width_att s = Width_Att_34 (s2b_escape s) width_att_bs = Width_Att_34 instance A_Width Att31 where width_att s = Width_Att_31 (s2b_escape s) width_att_bs = Width_Att_31 instance A_Width Att21 where width_att s = Width_Att_21 (s2b_escape s) width_att_bs = Width_Att_21 instance A_Width Att20 where width_att s = Width_Att_20 (s2b_escape s) width_att_bs = Width_Att_20 instance A_Width Att13 where width_att s = Width_Att_13 (s2b_escape s) width_att_bs = Width_Att_13 class A_Vlink a where vlink_att :: String -> a vlink_att_bs :: B.ByteString -> a instance A_Vlink Att14 where vlink_att s = Vlink_Att_14 (s2b_escape s) vlink_att_bs = Vlink_Att_14 class A_Ismap a where ismap_att :: String -> a instance A_Ismap Att37 where ismap_att s = Ismap_Att_37 (s2b (show s)) class A_Frame a where frame_att :: FrameEnum -> a instance A_Frame Att57 where frame_att s = Frame_Att_57 (s2b (show s)) class A_Size a where size_att :: String -> a size_att_bs :: B.ByteString -> a instance A_Size Att47 where size_att s = Size_Att_47 (s2b_escape s) size_att_bs = Size_Att_47 instance A_Size Att46 where size_att s = Size_Att_46 (s2b_escape s) size_att_bs = Size_Att_46 instance A_Size Att30 where size_att s = Size_Att_30 (s2b_escape s) size_att_bs = Size_Att_30 instance A_Size Att29 where size_att s = Size_Att_29 (s2b_escape s) size_att_bs = Size_Att_29 instance A_Size Att28 where size_att s = Size_Att_28 (s2b_escape s) size_att_bs = Size_Att_28 instance A_Size Att20 where size_att s = Size_Att_20 (s2b_escape s) size_att_bs = Size_Att_20 class A_Face a where face_att :: String -> a face_att_bs :: B.ByteString -> a instance A_Face Att30 where face_att s = Face_Att_30 (s2b_escape s) face_att_bs = Face_Att_30 instance A_Face Att28 where face_att s = Face_Att_28 (s2b_escape s) face_att_bs = Face_Att_28 class A_Bgcolor a where bgcolor_att :: String -> a bgcolor_att_bs :: B.ByteString -> a instance A_Bgcolor Att61 where bgcolor_att s = Bgcolor_Att_61 (s2b_escape s) bgcolor_att_bs = Bgcolor_Att_61 instance A_Bgcolor Att60 where bgcolor_att s = Bgcolor_Att_60 (s2b_escape s) bgcolor_att_bs = Bgcolor_Att_60 instance A_Bgcolor Att57 where bgcolor_att s = Bgcolor_Att_57 (s2b_escape s) bgcolor_att_bs = Bgcolor_Att_57 instance A_Bgcolor Att14 where bgcolor_att s = Bgcolor_Att_14 (s2b_escape s) bgcolor_att_bs = Bgcolor_Att_14 class A_Summary a where summary_att :: String -> a summary_att_bs :: B.ByteString -> a instance A_Summary Att57 where summary_att s = Summary_Att_57 (s2b_escape s) summary_att_bs = Summary_Att_57 class A_Text a where text_att :: String -> a text_att_bs :: B.ByteString -> a instance A_Text Att14 where text_att s = Text_Att_14 (s2b_escape s) text_att_bs = Text_Att_14 class A_Method a where method_att :: MethodEnum -> a instance A_Method Att43 where method_att s = Method_Att_43 (s2b (show s)) class A_Language a where language_att :: String -> a language_att_bs :: B.ByteString -> a instance A_Language Att9 where language_att s = Language_Att_9 (s2b_escape s) language_att_bs = Language_Att_9 class A_Tabindex a where tabindex_att :: String -> a tabindex_att_bs :: B.ByteString -> a instance A_Tabindex Att55 where tabindex_att s = Tabindex_Att_55 (s2b_escape s) tabindex_att_bs = Tabindex_Att_55 instance A_Tabindex Att51 where tabindex_att s = Tabindex_Att_51 (s2b_escape s) tabindex_att_bs = Tabindex_Att_51 instance A_Tabindex Att47 where tabindex_att s = Tabindex_Att_47 (s2b_escape s) tabindex_att_bs = Tabindex_Att_47 instance A_Tabindex Att46 where tabindex_att s = Tabindex_Att_46 (s2b_escape s) tabindex_att_bs = Tabindex_Att_46 instance A_Tabindex Att42 where tabindex_att s = Tabindex_Att_42 (s2b_escape s) tabindex_att_bs = Tabindex_Att_42 instance A_Tabindex Att31 where tabindex_att s = Tabindex_Att_31 (s2b_escape s) tabindex_att_bs = Tabindex_Att_31 instance A_Tabindex Att24 where tabindex_att s = Tabindex_Att_24 (s2b_escape s) tabindex_att_bs = Tabindex_Att_24 class A_Standby a where standby_att :: String -> a standby_att_bs :: B.ByteString -> a instance A_Standby Att31 where standby_att s = Standby_Att_31 (s2b_escape s) standby_att_bs = Standby_Att_31 class A_Onmousemove a where onmousemove_att :: String -> a onmousemove_att_bs :: B.ByteString -> a instance A_Onmousemove Att61 where onmousemove_att s = Onmousemove_Att_61 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_61 instance A_Onmousemove Att60 where onmousemove_att s = Onmousemove_Att_60 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_60 instance A_Onmousemove Att59 where onmousemove_att s = Onmousemove_Att_59 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_59 instance A_Onmousemove Att58 where onmousemove_att s = Onmousemove_Att_58 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_58 instance A_Onmousemove Att57 where onmousemove_att s = Onmousemove_Att_57 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_57 instance A_Onmousemove Att55 where onmousemove_att s = Onmousemove_Att_55 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_55 instance A_Onmousemove Att54 where onmousemove_att s = Onmousemove_Att_54 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_54 instance A_Onmousemove Att51 where onmousemove_att s = Onmousemove_Att_51 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_51 instance A_Onmousemove Att50 where onmousemove_att s = Onmousemove_Att_50 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_50 instance A_Onmousemove Att48 where onmousemove_att s = Onmousemove_Att_48 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_48 instance A_Onmousemove Att47 where onmousemove_att s = Onmousemove_Att_47 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_47 instance A_Onmousemove Att46 where onmousemove_att s = Onmousemove_Att_46 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_46 instance A_Onmousemove Att45 where onmousemove_att s = Onmousemove_Att_45 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_45 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 Att40 where onmousemove_att s = Onmousemove_Att_40 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_40 instance A_Onmousemove Att37 where onmousemove_att s = Onmousemove_Att_37 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_37 instance A_Onmousemove Att31 where onmousemove_att s = Onmousemove_Att_31 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_31 instance A_Onmousemove Att25 where onmousemove_att s = Onmousemove_Att_25 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_25 instance A_Onmousemove Att24 where onmousemove_att s = Onmousemove_Att_24 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_24 instance A_Onmousemove Att23 where onmousemove_att s = Onmousemove_Att_23 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_23 instance A_Onmousemove Att22 where onmousemove_att s = Onmousemove_Att_22 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_22 instance A_Onmousemove Att21 where onmousemove_att s = Onmousemove_Att_21 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_21 instance A_Onmousemove Att20 where onmousemove_att s = Onmousemove_Att_20 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_20 instance A_Onmousemove Att19 where onmousemove_att s = Onmousemove_Att_19 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_19 instance A_Onmousemove Att18 where onmousemove_att s = Onmousemove_Att_18 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_18 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 Att10 where onmousemove_att s = Onmousemove_Att_10 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_10 instance A_Onmousemove Att6 where onmousemove_att s = Onmousemove_Att_6 (s2b_escape s) onmousemove_att_bs = Onmousemove_Att_6 class A_Style a where style_att :: String -> a style_att_bs :: B.ByteString -> a instance A_Style Att61 where style_att s = Style_Att_61 (s2b_escape s) style_att_bs = Style_Att_61 instance A_Style Att60 where style_att s = Style_Att_60 (s2b_escape s) style_att_bs = Style_Att_60 instance A_Style Att59 where style_att s = Style_Att_59 (s2b_escape s) style_att_bs = Style_Att_59 instance A_Style Att58 where style_att s = Style_Att_58 (s2b_escape s) style_att_bs = Style_Att_58 instance A_Style Att57 where style_att s = Style_Att_57 (s2b_escape s) style_att_bs = Style_Att_57 instance A_Style Att56 where style_att s = Style_Att_56 (s2b_escape s) style_att_bs = Style_Att_56 instance A_Style Att55 where style_att s = Style_Att_55 (s2b_escape s) style_att_bs = Style_Att_55 instance A_Style Att54 where style_att s = Style_Att_54 (s2b_escape s) style_att_bs = Style_Att_54 instance A_Style Att51 where style_att s = Style_Att_51 (s2b_escape s) style_att_bs = Style_Att_51 instance A_Style Att50 where style_att s = Style_Att_50 (s2b_escape s) style_att_bs = Style_Att_50 instance A_Style Att48 where style_att s = Style_Att_48 (s2b_escape s) style_att_bs = Style_Att_48 instance A_Style Att47 where style_att s = Style_Att_47 (s2b_escape s) style_att_bs = Style_Att_47 instance A_Style Att46 where style_att s = Style_Att_46 (s2b_escape s) style_att_bs = Style_Att_46 instance A_Style Att45 where style_att s = Style_Att_45 (s2b_escape s) style_att_bs = Style_Att_45 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 Att40 where style_att s = Style_Att_40 (s2b_escape s) style_att_bs = Style_Att_40 instance A_Style Att37 where style_att s = Style_Att_37 (s2b_escape s) style_att_bs = Style_Att_37 instance A_Style Att34 where style_att s = Style_Att_34 (s2b_escape s) style_att_bs = Style_Att_34 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 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 Att24 where style_att s = Style_Att_24 (s2b_escape s) style_att_bs = Style_Att_24 instance A_Style Att23 where style_att s = Style_Att_23 (s2b_escape s) style_att_bs = Style_Att_23 instance A_Style Att22 where style_att s = Style_Att_22 (s2b_escape s) style_att_bs = Style_Att_22 instance A_Style Att21 where style_att s = Style_Att_21 (s2b_escape s) style_att_bs = Style_Att_21 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 Att18 where style_att s = Style_Att_18 (s2b_escape s) style_att_bs = Style_Att_18 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 Att10 where style_att s = Style_Att_10 (s2b_escape s) style_att_bs = Style_Att_10 instance A_Style Att6 where style_att s = Style_Att_6 (s2b_escape s) style_att_bs = Style_Att_6 class A_Codetype a where codetype_att :: String -> a codetype_att_bs :: B.ByteString -> a instance A_Codetype Att31 where codetype_att s = Codetype_Att_31 (s2b_escape s) codetype_att_bs = Codetype_Att_31 class A_Multiple a where multiple_att :: String -> a instance A_Multiple Att47 where multiple_att s = Multiple_Att_47 (s2b (show s)) 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_Ondblclick a where ondblclick_att :: String -> a ondblclick_att_bs :: B.ByteString -> a instance A_Ondblclick Att61 where ondblclick_att s = Ondblclick_Att_61 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_61 instance A_Ondblclick Att60 where ondblclick_att s = Ondblclick_Att_60 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_60 instance A_Ondblclick Att59 where ondblclick_att s = Ondblclick_Att_59 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_59 instance A_Ondblclick Att58 where ondblclick_att s = Ondblclick_Att_58 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_58 instance A_Ondblclick Att57 where ondblclick_att s = Ondblclick_Att_57 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_57 instance A_Ondblclick Att55 where ondblclick_att s = Ondblclick_Att_55 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_55 instance A_Ondblclick Att54 where ondblclick_att s = Ondblclick_Att_54 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_54 instance A_Ondblclick Att51 where ondblclick_att s = Ondblclick_Att_51 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_51 instance A_Ondblclick Att50 where ondblclick_att s = Ondblclick_Att_50 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_50 instance A_Ondblclick Att48 where ondblclick_att s = Ondblclick_Att_48 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_48 instance A_Ondblclick Att47 where ondblclick_att s = Ondblclick_Att_47 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_47 instance A_Ondblclick Att46 where ondblclick_att s = Ondblclick_Att_46 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_46 instance A_Ondblclick Att45 where ondblclick_att s = Ondblclick_Att_45 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_45 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 Att40 where ondblclick_att s = Ondblclick_Att_40 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_40 instance A_Ondblclick Att37 where ondblclick_att s = Ondblclick_Att_37 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_37 instance A_Ondblclick Att31 where ondblclick_att s = Ondblclick_Att_31 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_31 instance A_Ondblclick Att25 where ondblclick_att s = Ondblclick_Att_25 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_25 instance A_Ondblclick Att24 where ondblclick_att s = Ondblclick_Att_24 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_24 instance A_Ondblclick Att23 where ondblclick_att s = Ondblclick_Att_23 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_23 instance A_Ondblclick Att22 where ondblclick_att s = Ondblclick_Att_22 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_22 instance A_Ondblclick Att21 where ondblclick_att s = Ondblclick_Att_21 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_21 instance A_Ondblclick Att20 where ondblclick_att s = Ondblclick_Att_20 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_20 instance A_Ondblclick Att19 where ondblclick_att s = Ondblclick_Att_19 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_19 instance A_Ondblclick Att18 where ondblclick_att s = Ondblclick_Att_18 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_18 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 Att10 where ondblclick_att s = Ondblclick_Att_10 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_10 instance A_Ondblclick Att6 where ondblclick_att s = Ondblclick_Att_6 (s2b_escape s) ondblclick_att_bs = Ondblclick_Att_6 class A_Axis a where axis_att :: String -> a axis_att_bs :: B.ByteString -> a instance A_Axis Att61 where axis_att s = Axis_Att_61 (s2b_escape s) axis_att_bs = Axis_Att_61 class A_Cols a where cols_att :: String -> a cols_att_bs :: B.ByteString -> a instance A_Cols Att53 where cols_att s = Cols_Att_53 (s2b_escape s) cols_att_bs = Cols_Att_53 instance A_Cols Att51 where cols_att s = Cols_Att_51 (s2b_escape s) cols_att_bs = Cols_Att_51 instance A_Cols Att11 where cols_att s = Cols_Att_11 (s2b_escape s) cols_att_bs = Cols_Att_11 class A_Readonly a where readonly_att :: String -> a instance A_Readonly Att51 where readonly_att s = Readonly_Att_51 (s2b (show s)) instance A_Readonly Att46 where readonly_att s = Readonly_Att_46 (s2b (show s)) class A_Media a where media_att :: String -> a media_att_bs :: B.ByteString -> a instance A_Media Att7 where media_att s = Media_Att_7 (s2b_escape s) media_att_bs = Media_Att_7 instance A_Media Att6 where media_att s = Media_Att_6 (s2b_escape s) media_att_bs = Media_Att_6 class A_Compact a where compact_att :: String -> a instance A_Compact Att18 where compact_att s = Compact_Att_18 (s2b (show s)) instance A_Compact Att17 where compact_att s = Compact_Att_17 (s2b (show s)) instance A_Compact Att16 where compact_att s = Compact_Att_16 (s2b (show s)) class A_Src a where src_att :: String -> a src_att_bs :: B.ByteString -> a instance A_Src Att46 where src_att s = Src_Att_46 (s2b_escape s) src_att_bs = Src_Att_46 instance A_Src Att38 where src_att s = Src_Att_38 (s2b_escape s) src_att_bs = Src_Att_38 instance A_Src Att37 where src_att s = Src_Att_37 (s2b_escape s) src_att_bs = Src_Att_37 instance A_Src Att13 where src_att s = Src_Att_13 (s2b_escape s) src_att_bs = Src_Att_13 instance A_Src Att12 where src_att s = Src_Att_12 (s2b_escape s) src_att_bs = Src_Att_12 instance A_Src Att9 where src_att s = Src_Att_9 (s2b_escape s) src_att_bs = Src_Att_9 class A_For a where for_att :: String -> a for_att_bs :: B.ByteString -> a instance A_For Att45 where for_att s = For_Att_45 (s2b_escape s) for_att_bs = For_Att_45 class A_Hreflang a where hreflang_att :: String -> a hreflang_att_bs :: B.ByteString -> a instance A_Hreflang Att24 where hreflang_att s = Hreflang_Att_24 (s2b_escape s) hreflang_att_bs = Hreflang_Att_24 instance A_Hreflang Att6 where hreflang_att s = Hreflang_Att_6 (s2b_escape s) hreflang_att_bs = Hreflang_Att_6 class A_Checked a where checked_att :: String -> a instance A_Checked Att46 where checked_att s = Checked_Att_46 (s2b (show s)) class A_Onkeypress a where onkeypress_att :: String -> a onkeypress_att_bs :: B.ByteString -> a instance A_Onkeypress Att61 where onkeypress_att s = Onkeypress_Att_61 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_61 instance A_Onkeypress Att60 where onkeypress_att s = Onkeypress_Att_60 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_60 instance A_Onkeypress Att59 where onkeypress_att s = Onkeypress_Att_59 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_59 instance A_Onkeypress Att58 where onkeypress_att s = Onkeypress_Att_58 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_58 instance A_Onkeypress Att57 where onkeypress_att s = Onkeypress_Att_57 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_57 instance A_Onkeypress Att55 where onkeypress_att s = Onkeypress_Att_55 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_55 instance A_Onkeypress Att54 where onkeypress_att s = Onkeypress_Att_54 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_54 instance A_Onkeypress Att51 where onkeypress_att s = Onkeypress_Att_51 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_51 instance A_Onkeypress Att50 where onkeypress_att s = Onkeypress_Att_50 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_50 instance A_Onkeypress Att48 where onkeypress_att s = Onkeypress_Att_48 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_48 instance A_Onkeypress Att47 where onkeypress_att s = Onkeypress_Att_47 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_47 instance A_Onkeypress Att46 where onkeypress_att s = Onkeypress_Att_46 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_46 instance A_Onkeypress Att45 where onkeypress_att s = Onkeypress_Att_45 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_45 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 Att40 where onkeypress_att s = Onkeypress_Att_40 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_40 instance A_Onkeypress Att37 where onkeypress_att s = Onkeypress_Att_37 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_37 instance A_Onkeypress Att31 where onkeypress_att s = Onkeypress_Att_31 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_31 instance A_Onkeypress Att25 where onkeypress_att s = Onkeypress_Att_25 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_25 instance A_Onkeypress Att24 where onkeypress_att s = Onkeypress_Att_24 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_24 instance A_Onkeypress Att23 where onkeypress_att s = Onkeypress_Att_23 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_23 instance A_Onkeypress Att22 where onkeypress_att s = Onkeypress_Att_22 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_22 instance A_Onkeypress Att21 where onkeypress_att s = Onkeypress_Att_21 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_21 instance A_Onkeypress Att20 where onkeypress_att s = Onkeypress_Att_20 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_20 instance A_Onkeypress Att19 where onkeypress_att s = Onkeypress_Att_19 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_19 instance A_Onkeypress Att18 where onkeypress_att s = Onkeypress_Att_18 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_18 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 Att10 where onkeypress_att s = Onkeypress_Att_10 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_10 instance A_Onkeypress Att6 where onkeypress_att s = Onkeypress_Att_6 (s2b_escape s) onkeypress_att_bs = Onkeypress_Att_6 class A_Class a where class_att :: String -> a class_att_bs :: B.ByteString -> a instance A_Class Att61 where class_att s = Class_Att_61 (s2b_escape s) class_att_bs = Class_Att_61 instance A_Class Att60 where class_att s = Class_Att_60 (s2b_escape s) class_att_bs = Class_Att_60 instance A_Class Att59 where class_att s = Class_Att_59 (s2b_escape s) class_att_bs = Class_Att_59 instance A_Class Att58 where class_att s = Class_Att_58 (s2b_escape s) class_att_bs = Class_Att_58 instance A_Class Att57 where class_att s = Class_Att_57 (s2b_escape s) class_att_bs = Class_Att_57 instance A_Class Att56 where class_att s = Class_Att_56 (s2b_escape s) class_att_bs = Class_Att_56 instance A_Class Att55 where class_att s = Class_Att_55 (s2b_escape s) class_att_bs = Class_Att_55 instance A_Class Att54 where class_att s = Class_Att_54 (s2b_escape s) class_att_bs = Class_Att_54 instance A_Class Att51 where class_att s = Class_Att_51 (s2b_escape s) class_att_bs = Class_Att_51 instance A_Class Att50 where class_att s = Class_Att_50 (s2b_escape s) class_att_bs = Class_Att_50 instance A_Class Att48 where class_att s = Class_Att_48 (s2b_escape s) class_att_bs = Class_Att_48 instance A_Class Att47 where class_att s = Class_Att_47 (s2b_escape s) class_att_bs = Class_Att_47 instance A_Class Att46 where class_att s = Class_Att_46 (s2b_escape s) class_att_bs = Class_Att_46 instance A_Class Att45 where class_att s = Class_Att_45 (s2b_escape s) class_att_bs = Class_Att_45 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 Att40 where class_att s = Class_Att_40 (s2b_escape s) class_att_bs = Class_Att_40 instance A_Class Att37 where class_att s = Class_Att_37 (s2b_escape s) class_att_bs = Class_Att_37 instance A_Class Att34 where class_att s = Class_Att_34 (s2b_escape s) class_att_bs = Class_Att_34 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 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 Att24 where class_att s = Class_Att_24 (s2b_escape s) class_att_bs = Class_Att_24 instance A_Class Att23 where class_att s = Class_Att_23 (s2b_escape s) class_att_bs = Class_Att_23 instance A_Class Att22 where class_att s = Class_Att_22 (s2b_escape s) class_att_bs = Class_Att_22 instance A_Class Att21 where class_att s = Class_Att_21 (s2b_escape s) class_att_bs = Class_Att_21 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 Att18 where class_att s = Class_Att_18 (s2b_escape s) class_att_bs = Class_Att_18 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 Att10 where class_att s = Class_Att_10 (s2b_escape s) class_att_bs = Class_Att_10 instance A_Class Att6 where class_att s = Class_Att_6 (s2b_escape s) class_att_bs = Class_Att_6 class A_Shape a where shape_att :: ShapeEnum -> a instance A_Shape Att42 where shape_att s = Shape_Att_42 (s2b (show s)) instance A_Shape Att24 where shape_att s = Shape_Att_24 (s2b (show s)) class A_Label a where label_att :: String -> a label_att_bs :: B.ByteString -> a instance A_Label Att50 where label_att s = Label_Att_50 (s2b_escape s) label_att_bs = Label_Att_50 instance A_Label Att49 where label_att s = Label_Att_49 (s2b_escape s) label_att_bs = Label_Att_49 instance A_Label Att48 where label_att s = Label_Att_48 (s2b_escape s) label_att_bs = Label_Att_48 class A_Accesskey a where accesskey_att :: String -> a accesskey_att_bs :: B.ByteString -> a instance A_Accesskey Att55 where accesskey_att s = Accesskey_Att_55 (s2b_escape s) accesskey_att_bs = Accesskey_Att_55 instance A_Accesskey Att54 where accesskey_att s = Accesskey_Att_54 (s2b_escape s) accesskey_att_bs = Accesskey_Att_54 instance A_Accesskey Att51 where accesskey_att s = Accesskey_Att_51 (s2b_escape s) accesskey_att_bs = Accesskey_Att_51 instance A_Accesskey Att46 where accesskey_att s = Accesskey_Att_46 (s2b_escape s) accesskey_att_bs = Accesskey_Att_46 instance A_Accesskey Att45 where accesskey_att s = Accesskey_Att_45 (s2b_escape s) accesskey_att_bs = Accesskey_Att_45 instance A_Accesskey Att42 where accesskey_att s = Accesskey_Att_42 (s2b_escape s) accesskey_att_bs = Accesskey_Att_42 instance A_Accesskey Att24 where accesskey_att s = Accesskey_Att_24 (s2b_escape s) accesskey_att_bs = Accesskey_Att_24 class A_Disabled a where disabled_att :: String -> a instance A_Disabled Att55 where disabled_att s = Disabled_Att_55 (s2b (show s)) instance A_Disabled Att51 where disabled_att s = Disabled_Att_51 (s2b (show s)) instance A_Disabled Att50 where disabled_att s = Disabled_Att_50 (s2b (show s)) instance A_Disabled Att48 where disabled_att s = Disabled_Att_48 (s2b (show s)) instance A_Disabled Att47 where disabled_att s = Disabled_Att_47 (s2b (show s)) instance A_Disabled Att46 where disabled_att s = Disabled_Att_46 (s2b (show s)) class A_Scrolling a where scrolling_att :: ScrollingEnum -> a instance A_Scrolling Att13 where scrolling_att s = Scrolling_Att_13 (s2b (show s)) instance A_Scrolling Att12 where scrolling_att s = Scrolling_Att_12 (s2b (show s)) class A_Rows a where rows_att :: String -> a rows_att_bs :: B.ByteString -> a instance A_Rows Att52 where rows_att s = Rows_Att_52 (s2b_escape s) rows_att_bs = Rows_Att_52 instance A_Rows Att51 where rows_att s = Rows_Att_51 (s2b_escape s) rows_att_bs = Rows_Att_51 instance A_Rows Att11 where rows_att s = Rows_Att_11 (s2b_escape s) rows_att_bs = Rows_Att_11 class A_Rules a where rules_att :: RulesEnum -> a instance A_Rules Att57 where rules_att s = Rules_Att_57 (s2b (show s)) class A_Onfocus a where onfocus_att :: String -> a onfocus_att_bs :: B.ByteString -> a instance A_Onfocus Att55 where onfocus_att s = Onfocus_Att_55 (s2b_escape s) onfocus_att_bs = Onfocus_Att_55 instance A_Onfocus Att51 where onfocus_att s = Onfocus_Att_51 (s2b_escape s) onfocus_att_bs = Onfocus_Att_51 instance A_Onfocus Att47 where onfocus_att s = Onfocus_Att_47 (s2b_escape s) onfocus_att_bs = Onfocus_Att_47 instance A_Onfocus Att46 where onfocus_att s = Onfocus_Att_46 (s2b_escape s) onfocus_att_bs = Onfocus_Att_46 instance A_Onfocus Att45 where onfocus_att s = Onfocus_Att_45 (s2b_escape s) onfocus_att_bs = Onfocus_Att_45 instance A_Onfocus Att42 where onfocus_att s = Onfocus_Att_42 (s2b_escape s) onfocus_att_bs = Onfocus_Att_42 instance A_Onfocus Att24 where onfocus_att s = Onfocus_Att_24 (s2b_escape s) onfocus_att_bs = Onfocus_Att_24 class A_Alink a where alink_att :: String -> a alink_att_bs :: B.ByteString -> a instance A_Alink Att14 where alink_att s = Alink_Att_14 (s2b_escape s) alink_att_bs = Alink_Att_14 class A_Colspan a where colspan_att :: String -> a colspan_att_bs :: B.ByteString -> a instance A_Colspan Att61 where colspan_att s = Colspan_Att_61 (s2b_escape s) colspan_att_bs = Colspan_Att_61 class A_Cite a where cite_att :: String -> a cite_att_bs :: B.ByteString -> a instance A_Cite Att23 where cite_att s = Cite_Att_23 (s2b_escape s) cite_att_bs = Cite_Att_23 instance A_Cite Att22 where cite_att s = Cite_Att_22 (s2b_escape s) cite_att_bs = Cite_Att_22 class A_Marginheight a where marginheight_att :: String -> a marginheight_att_bs :: B.ByteString -> a instance A_Marginheight Att13 where marginheight_att s = Marginheight_Att_13 (s2b_escape s) marginheight_att_bs = Marginheight_Att_13 instance A_Marginheight Att12 where marginheight_att s = Marginheight_Att_12 (s2b_escape s) marginheight_att_bs = Marginheight_Att_12 class A_Link a where link_att :: String -> a link_att_bs :: B.ByteString -> a instance A_Link Att14 where link_att s = Link_Att_14 (s2b_escape s) link_att_bs = Link_Att_14 class A_Maxlength a where maxlength_att :: String -> a maxlength_att_bs :: B.ByteString -> a instance A_Maxlength Att46 where maxlength_att s = Maxlength_Att_46 (s2b_escape s) maxlength_att_bs = Maxlength_Att_46 class A_Onselect a where onselect_att :: String -> a onselect_att_bs :: B.ByteString -> a instance A_Onselect Att51 where onselect_att s = Onselect_Att_51 (s2b_escape s) onselect_att_bs = Onselect_Att_51 instance A_Onselect Att46 where onselect_att s = Onselect_Att_46 (s2b_escape s) onselect_att_bs = Onselect_Att_46 class A_Archive a where archive_att :: String -> a archive_att_bs :: B.ByteString -> a instance A_Archive Att34 where archive_att s = Archive_Att_34 (s2b_escape s) archive_att_bs = Archive_Att_34 instance A_Archive Att31 where archive_att s = Archive_Att_31 (s2b_escape s) archive_att_bs = Archive_Att_31 class A_Longdesc a where longdesc_att :: String -> a longdesc_att_bs :: B.ByteString -> a instance A_Longdesc Att37 where longdesc_att s = Longdesc_Att_37 (s2b_escape s) longdesc_att_bs = Longdesc_Att_37 instance A_Longdesc Att13 where longdesc_att s = Longdesc_Att_13 (s2b_escape s) longdesc_att_bs = Longdesc_Att_13 instance A_Longdesc Att12 where longdesc_att s = Longdesc_Att_12 (s2b_escape s) longdesc_att_bs = Longdesc_Att_12 class A_Classid a where classid_att :: String -> a classid_att_bs :: B.ByteString -> a instance A_Classid Att31 where classid_att s = Classid_Att_31 (s2b_escape s) classid_att_bs = Classid_Att_31 class A_Space a where space_att :: String -> a instance A_Space Att21 where space_att s = Space_Att_21 (s2b (show s)) instance A_Space Att9 where space_att s = Space_Att_9 (s2b (show s)) instance A_Space Att7 where space_att s = Space_Att_7 (s2b (show s)) class A_Noshade a where noshade_att :: String -> a instance A_Noshade Att20 where noshade_att s = Noshade_Att_20 (s2b (show s)) class A_Hspace a where hspace_att :: String -> a hspace_att_bs :: B.ByteString -> a instance A_Hspace Att37 where hspace_att s = Hspace_Att_37 (s2b_escape s) hspace_att_bs = Hspace_Att_37 instance A_Hspace Att34 where hspace_att s = Hspace_Att_34 (s2b_escape s) hspace_att_bs = Hspace_Att_34 instance A_Hspace Att31 where hspace_att s = Hspace_Att_31 (s2b_escape s) hspace_att_bs = Hspace_Att_31 class A_Onload a where onload_att :: String -> a onload_att_bs :: B.ByteString -> a instance A_Onload Att14 where onload_att s = Onload_Att_14 (s2b_escape s) onload_att_bs = Onload_Att_14 instance A_Onload Att11 where onload_att s = Onload_Att_11 (s2b_escape s) onload_att_bs = Onload_Att_11 class A_Action a where action_att :: String -> a action_att_bs :: B.ByteString -> a instance A_Action Att44 where action_att s = Action_Att_44 (s2b_escape s) action_att_bs = Action_Att_44 instance A_Action Att43 where action_att s = Action_Att_43 (s2b_escape s) action_att_bs = Action_Att_43 class A_Selected a where selected_att :: String -> a instance A_Selected Att50 where selected_att s = Selected_Att_50 (s2b (show s)) class RenderAttribute a where renderAtt :: a -> (B.ByteString,B.ByteString) instance RenderAttribute Att61 where renderAtt (Id_Att_61 b) = (id_byte,b) renderAtt (Class_Att_61 b) = (class_byte,b) renderAtt (Style_Att_61 b) = (style_byte,b) renderAtt (Title_Att_61 b) = (title_byte,b) renderAtt (Lang_Att_61 b) = (lang_byte,b) renderAtt (Dir_Att_61 b) = (dir_byte,b) renderAtt (Onclick_Att_61 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_61 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_61 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_61 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_61 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_61 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_61 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_61 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_61 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_61 b) = (onkeyup_byte,b) renderAtt (Abbr_Att_61 b) = (abbr_byte,b) renderAtt (Axis_Att_61 b) = (axis_byte,b) renderAtt (Headers_Att_61 b) = (headers_byte,b) renderAtt (Scope_Att_61 b) = (scope_byte,b) renderAtt (Rowspan_Att_61 b) = (rowspan_byte,b) renderAtt (Colspan_Att_61 b) = (colspan_byte,b) renderAtt (Align_Att_61 b) = (align_byte,b) renderAtt (Char_Att_61 b) = (char_byte,b) renderAtt (Charoff_Att_61 b) = (charoff_byte,b) renderAtt (Valign_Att_61 b) = (valign_byte,b) renderAtt (Nowrap_Att_61 b) = (nowrap_byte,b) renderAtt (Bgcolor_Att_61 b) = (bgcolor_byte,b) renderAtt (Width_Att_61 b) = (width_byte,b) renderAtt (Height_Att_61 b) = (height_byte,b) instance RenderAttribute Att60 where renderAtt (Id_Att_60 b) = (id_byte,b) renderAtt (Class_Att_60 b) = (class_byte,b) renderAtt (Style_Att_60 b) = (style_byte,b) renderAtt (Title_Att_60 b) = (title_byte,b) renderAtt (Lang_Att_60 b) = (lang_byte,b) renderAtt (Dir_Att_60 b) = (dir_byte,b) renderAtt (Onclick_Att_60 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_60 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_60 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_60 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_60 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_60 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_60 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_60 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_60 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_60 b) = (onkeyup_byte,b) renderAtt (Align_Att_60 b) = (align_byte,b) renderAtt (Char_Att_60 b) = (char_byte,b) renderAtt (Charoff_Att_60 b) = (charoff_byte,b) renderAtt (Valign_Att_60 b) = (valign_byte,b) renderAtt (Bgcolor_Att_60 b) = (bgcolor_byte,b) instance RenderAttribute Att59 where renderAtt (Id_Att_59 b) = (id_byte,b) renderAtt (Class_Att_59 b) = (class_byte,b) renderAtt (Style_Att_59 b) = (style_byte,b) renderAtt (Title_Att_59 b) = (title_byte,b) renderAtt (Lang_Att_59 b) = (lang_byte,b) renderAtt (Dir_Att_59 b) = (dir_byte,b) renderAtt (Onclick_Att_59 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_59 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_59 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_59 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_59 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_59 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_59 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_59 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_59 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_59 b) = (onkeyup_byte,b) renderAtt (Span_Att_59 b) = (span_byte,b) renderAtt (Width_Att_59 b) = (width_byte,b) renderAtt (Align_Att_59 b) = (align_byte,b) renderAtt (Char_Att_59 b) = (char_byte,b) renderAtt (Charoff_Att_59 b) = (charoff_byte,b) renderAtt (Valign_Att_59 b) = (valign_byte,b) instance RenderAttribute Att58 where renderAtt (Id_Att_58 b) = (id_byte,b) renderAtt (Class_Att_58 b) = (class_byte,b) renderAtt (Style_Att_58 b) = (style_byte,b) renderAtt (Title_Att_58 b) = (title_byte,b) renderAtt (Lang_Att_58 b) = (lang_byte,b) renderAtt (Dir_Att_58 b) = (dir_byte,b) renderAtt (Onclick_Att_58 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_58 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_58 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_58 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_58 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_58 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_58 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_58 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_58 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_58 b) = (onkeyup_byte,b) renderAtt (Align_Att_58 b) = (align_byte,b) renderAtt (Char_Att_58 b) = (char_byte,b) renderAtt (Charoff_Att_58 b) = (charoff_byte,b) renderAtt (Valign_Att_58 b) = (valign_byte,b) instance RenderAttribute Att57 where renderAtt (Id_Att_57 b) = (id_byte,b) renderAtt (Class_Att_57 b) = (class_byte,b) renderAtt (Style_Att_57 b) = (style_byte,b) renderAtt (Title_Att_57 b) = (title_byte,b) renderAtt (Lang_Att_57 b) = (lang_byte,b) renderAtt (Dir_Att_57 b) = (dir_byte,b) renderAtt (Onclick_Att_57 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_57 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_57 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_57 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_57 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_57 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_57 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_57 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_57 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_57 b) = (onkeyup_byte,b) renderAtt (Summary_Att_57 b) = (summary_byte,b) renderAtt (Width_Att_57 b) = (width_byte,b) renderAtt (Border_Att_57 b) = (border_byte,b) renderAtt (Frame_Att_57 b) = (frame_byte,b) renderAtt (Rules_Att_57 b) = (rules_byte,b) renderAtt (Cellspacing_Att_57 b) = (cellspacing_byte,b) renderAtt (Cellpadding_Att_57 b) = (cellpadding_byte,b) renderAtt (Align_Att_57 b) = (align_byte,b) renderAtt (Bgcolor_Att_57 b) = (bgcolor_byte,b) instance RenderAttribute Att56 where renderAtt (Id_Att_56 b) = (id_byte,b) renderAtt (Class_Att_56 b) = (class_byte,b) renderAtt (Style_Att_56 b) = (style_byte,b) renderAtt (Title_Att_56 b) = (title_byte,b) renderAtt (Lang_Att_56 b) = (lang_byte,b) renderAtt (Dir_Att_56 b) = (dir_byte,b) renderAtt (Prompt_Att_56 b) = (prompt_byte,b) instance RenderAttribute Att55 where renderAtt (Id_Att_55 b) = (id_byte,b) renderAtt (Class_Att_55 b) = (class_byte,b) renderAtt (Style_Att_55 b) = (style_byte,b) renderAtt (Title_Att_55 b) = (title_byte,b) renderAtt (Lang_Att_55 b) = (lang_byte,b) renderAtt (Dir_Att_55 b) = (dir_byte,b) renderAtt (Onclick_Att_55 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_55 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_55 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_55 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_55 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_55 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_55 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_55 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_55 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_55 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_55 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_55 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_55 b) = (onfocus_byte,b) renderAtt (Onblur_Att_55 b) = (onblur_byte,b) renderAtt (Name_Att_55 b) = (name_byte,b) renderAtt (Value_Att_55 b) = (value_byte,b) renderAtt (Type_Att_55 b) = (type_byte,b) renderAtt (Disabled_Att_55 b) = (disabled_byte,b) instance RenderAttribute Att54 where renderAtt (Id_Att_54 b) = (id_byte,b) renderAtt (Class_Att_54 b) = (class_byte,b) renderAtt (Style_Att_54 b) = (style_byte,b) renderAtt (Title_Att_54 b) = (title_byte,b) renderAtt (Lang_Att_54 b) = (lang_byte,b) renderAtt (Dir_Att_54 b) = (dir_byte,b) renderAtt (Onclick_Att_54 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_54 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_54 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_54 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_54 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_54 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_54 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_54 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_54 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_54 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_54 b) = (accesskey_byte,b) renderAtt (Align_Att_54 b) = (align_byte,b) instance RenderAttribute Att53 where renderAtt (Cols_Att_53 b) = (cols_byte,b) instance RenderAttribute Att52 where renderAtt (Rows_Att_52 b) = (rows_byte,b) instance RenderAttribute Att51 where renderAtt (Id_Att_51 b) = (id_byte,b) renderAtt (Class_Att_51 b) = (class_byte,b) renderAtt (Style_Att_51 b) = (style_byte,b) renderAtt (Title_Att_51 b) = (title_byte,b) renderAtt (Lang_Att_51 b) = (lang_byte,b) renderAtt (Dir_Att_51 b) = (dir_byte,b) renderAtt (Onclick_Att_51 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_51 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_51 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_51 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_51 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_51 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_51 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_51 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_51 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_51 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_51 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_51 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_51 b) = (onfocus_byte,b) renderAtt (Onblur_Att_51 b) = (onblur_byte,b) renderAtt (Name_Att_51 b) = (name_byte,b) renderAtt (Rows_Att_51 b) = (rows_byte,b) renderAtt (Cols_Att_51 b) = (cols_byte,b) renderAtt (Disabled_Att_51 b) = (disabled_byte,b) renderAtt (Readonly_Att_51 b) = (readonly_byte,b) renderAtt (Onselect_Att_51 b) = (onselect_byte,b) renderAtt (Onchange_Att_51 b) = (onchange_byte,b) instance RenderAttribute Att50 where renderAtt (Id_Att_50 b) = (id_byte,b) renderAtt (Class_Att_50 b) = (class_byte,b) renderAtt (Style_Att_50 b) = (style_byte,b) renderAtt (Title_Att_50 b) = (title_byte,b) renderAtt (Lang_Att_50 b) = (lang_byte,b) renderAtt (Dir_Att_50 b) = (dir_byte,b) renderAtt (Onclick_Att_50 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_50 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_50 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_50 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_50 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_50 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_50 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_50 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_50 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_50 b) = (onkeyup_byte,b) renderAtt (Selected_Att_50 b) = (selected_byte,b) renderAtt (Disabled_Att_50 b) = (disabled_byte,b) renderAtt (Label_Att_50 b) = (label_byte,b) renderAtt (Value_Att_50 b) = (value_byte,b) instance RenderAttribute Att49 where renderAtt (Label_Att_49 b) = (label_byte,b) instance RenderAttribute Att48 where renderAtt (Id_Att_48 b) = (id_byte,b) renderAtt (Class_Att_48 b) = (class_byte,b) renderAtt (Style_Att_48 b) = (style_byte,b) renderAtt (Title_Att_48 b) = (title_byte,b) renderAtt (Lang_Att_48 b) = (lang_byte,b) renderAtt (Dir_Att_48 b) = (dir_byte,b) renderAtt (Onclick_Att_48 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_48 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_48 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_48 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_48 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_48 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_48 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_48 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_48 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_48 b) = (onkeyup_byte,b) renderAtt (Disabled_Att_48 b) = (disabled_byte,b) renderAtt (Label_Att_48 b) = (label_byte,b) instance RenderAttribute Att47 where renderAtt (Id_Att_47 b) = (id_byte,b) renderAtt (Class_Att_47 b) = (class_byte,b) renderAtt (Style_Att_47 b) = (style_byte,b) renderAtt (Title_Att_47 b) = (title_byte,b) renderAtt (Lang_Att_47 b) = (lang_byte,b) renderAtt (Dir_Att_47 b) = (dir_byte,b) renderAtt (Onclick_Att_47 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_47 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_47 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_47 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_47 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_47 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_47 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_47 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_47 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_47 b) = (onkeyup_byte,b) renderAtt (Name_Att_47 b) = (name_byte,b) renderAtt (Size_Att_47 b) = (size_byte,b) renderAtt (Multiple_Att_47 b) = (multiple_byte,b) renderAtt (Disabled_Att_47 b) = (disabled_byte,b) renderAtt (Tabindex_Att_47 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_47 b) = (onfocus_byte,b) renderAtt (Onblur_Att_47 b) = (onblur_byte,b) renderAtt (Onchange_Att_47 b) = (onchange_byte,b) instance RenderAttribute Att46 where renderAtt (Id_Att_46 b) = (id_byte,b) renderAtt (Class_Att_46 b) = (class_byte,b) renderAtt (Style_Att_46 b) = (style_byte,b) renderAtt (Title_Att_46 b) = (title_byte,b) renderAtt (Lang_Att_46 b) = (lang_byte,b) renderAtt (Dir_Att_46 b) = (dir_byte,b) renderAtt (Onclick_Att_46 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_46 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_46 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_46 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_46 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_46 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_46 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_46 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_46 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_46 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_46 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_46 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_46 b) = (onfocus_byte,b) renderAtt (Onblur_Att_46 b) = (onblur_byte,b) renderAtt (Type_Att_46 b) = (type_byte,b) renderAtt (Name_Att_46 b) = (name_byte,b) renderAtt (Value_Att_46 b) = (value_byte,b) renderAtt (Checked_Att_46 b) = (checked_byte,b) renderAtt (Disabled_Att_46 b) = (disabled_byte,b) renderAtt (Readonly_Att_46 b) = (readonly_byte,b) renderAtt (Size_Att_46 b) = (size_byte,b) renderAtt (Maxlength_Att_46 b) = (maxlength_byte,b) renderAtt (Src_Att_46 b) = (src_byte,b) renderAtt (Alt_Att_46 b) = (alt_byte,b) renderAtt (Usemap_Att_46 b) = (usemap_byte,b) renderAtt (Onselect_Att_46 b) = (onselect_byte,b) renderAtt (Onchange_Att_46 b) = (onchange_byte,b) renderAtt (Accept_Att_46 b) = (accept_byte,b) renderAtt (Align_Att_46 b) = (align_byte,b) instance RenderAttribute Att45 where renderAtt (Id_Att_45 b) = (id_byte,b) renderAtt (Class_Att_45 b) = (class_byte,b) renderAtt (Style_Att_45 b) = (style_byte,b) renderAtt (Title_Att_45 b) = (title_byte,b) renderAtt (Lang_Att_45 b) = (lang_byte,b) renderAtt (Dir_Att_45 b) = (dir_byte,b) renderAtt (Onclick_Att_45 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_45 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_45 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_45 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_45 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_45 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_45 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_45 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_45 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_45 b) = (onkeyup_byte,b) renderAtt (For_Att_45 b) = (for_byte,b) renderAtt (Accesskey_Att_45 b) = (accesskey_byte,b) renderAtt (Onfocus_Att_45 b) = (onfocus_byte,b) renderAtt (Onblur_Att_45 b) = (onblur_byte,b) instance RenderAttribute Att44 where renderAtt (Action_Att_44 b) = (action_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 (Action_Att_43 b) = (action_byte,b) renderAtt (Method_Att_43 b) = (method_byte,b) renderAtt (Name_Att_43 b) = (name_byte,b) renderAtt (Enctype_Att_43 b) = (enctype_byte,b) renderAtt (Onsubmit_Att_43 b) = (onsubmit_byte,b) renderAtt (Onreset_Att_43 b) = (onreset_byte,b) renderAtt (Accept_Att_43 b) = (accept_byte,b) renderAtt (Accept_charset_Att_43 b) = (accept_charset_byte,b) renderAtt (Target_Att_43 b) = (target_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 (Accesskey_Att_42 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_42 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_42 b) = (onfocus_byte,b) renderAtt (Onblur_Att_42 b) = (onblur_byte,b) renderAtt (Shape_Att_42 b) = (shape_byte,b) renderAtt (Coords_Att_42 b) = (coords_byte,b) renderAtt (Href_Att_42 b) = (href_byte,b) renderAtt (Nohref_Att_42 b) = (nohref_byte,b) renderAtt (Alt_Att_42 b) = (alt_byte,b) renderAtt (Target_Att_42 b) = (target_byte,b) instance RenderAttribute Att41 where renderAtt (Id_Att_41 b) = (id_byte,b) instance RenderAttribute Att40 where 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 (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 (Name_Att_40 b) = (name_byte,b) instance RenderAttribute Att39 where renderAtt (Alt_Att_39 b) = (alt_byte,b) instance RenderAttribute Att38 where renderAtt (Src_Att_38 b) = (src_byte,b) instance RenderAttribute Att37 where renderAtt (Id_Att_37 b) = (id_byte,b) renderAtt (Class_Att_37 b) = (class_byte,b) renderAtt (Style_Att_37 b) = (style_byte,b) renderAtt (Title_Att_37 b) = (title_byte,b) renderAtt (Lang_Att_37 b) = (lang_byte,b) renderAtt (Dir_Att_37 b) = (dir_byte,b) renderAtt (Onclick_Att_37 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_37 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_37 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_37 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_37 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_37 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_37 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_37 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_37 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_37 b) = (onkeyup_byte,b) renderAtt (Src_Att_37 b) = (src_byte,b) renderAtt (Alt_Att_37 b) = (alt_byte,b) renderAtt (Name_Att_37 b) = (name_byte,b) renderAtt (Longdesc_Att_37 b) = (longdesc_byte,b) renderAtt (Height_Att_37 b) = (height_byte,b) renderAtt (Width_Att_37 b) = (width_byte,b) renderAtt (Usemap_Att_37 b) = (usemap_byte,b) renderAtt (Ismap_Att_37 b) = (ismap_byte,b) renderAtt (Align_Att_37 b) = (align_byte,b) renderAtt (Border_Att_37 b) = (border_byte,b) renderAtt (Hspace_Att_37 b) = (hspace_byte,b) renderAtt (Vspace_Att_37 b) = (vspace_byte,b) instance RenderAttribute Att36 where renderAtt (Height_Att_36 b) = (height_byte,b) instance RenderAttribute Att35 where renderAtt (Width_Att_35 b) = (width_byte,b) instance RenderAttribute Att34 where renderAtt (Id_Att_34 b) = (id_byte,b) renderAtt (Class_Att_34 b) = (class_byte,b) renderAtt (Style_Att_34 b) = (style_byte,b) renderAtt (Title_Att_34 b) = (title_byte,b) renderAtt (Codebase_Att_34 b) = (codebase_byte,b) renderAtt (Archive_Att_34 b) = (archive_byte,b) renderAtt (Code_Att_34 b) = (code_byte,b) renderAtt (Object_Att_34 b) = (object_byte,b) renderAtt (Alt_Att_34 b) = (alt_byte,b) renderAtt (Name_Att_34 b) = (name_byte,b) renderAtt (Width_Att_34 b) = (width_byte,b) renderAtt (Height_Att_34 b) = (height_byte,b) renderAtt (Align_Att_34 b) = (align_byte,b) renderAtt (Hspace_Att_34 b) = (hspace_byte,b) renderAtt (Vspace_Att_34 b) = (vspace_byte,b) instance RenderAttribute Att33 where renderAtt (Name_Att_33 b) = (name_byte,b) instance RenderAttribute Att32 where renderAtt (Id_Att_32 b) = (id_byte,b) renderAtt (Name_Att_32 b) = (name_byte,b) renderAtt (Value_Att_32 b) = (value_byte,b) renderAtt (Valuetype_Att_32 b) = (valuetype_byte,b) renderAtt (Type_Att_32 b) = (type_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 (Declare_Att_31 b) = (declare_byte,b) renderAtt (Classid_Att_31 b) = (classid_byte,b) renderAtt (Codebase_Att_31 b) = (codebase_byte,b) renderAtt (Data_Att_31 b) = (data_byte,b) renderAtt (Type_Att_31 b) = (type_byte,b) renderAtt (Codetype_Att_31 b) = (codetype_byte,b) renderAtt (Archive_Att_31 b) = (archive_byte,b) renderAtt (Standby_Att_31 b) = (standby_byte,b) renderAtt (Height_Att_31 b) = (height_byte,b) renderAtt (Width_Att_31 b) = (width_byte,b) renderAtt (Usemap_Att_31 b) = (usemap_byte,b) renderAtt (Name_Att_31 b) = (name_byte,b) renderAtt (Tabindex_Att_31 b) = (tabindex_byte,b) renderAtt (Align_Att_31 b) = (align_byte,b) renderAtt (Border_Att_31 b) = (border_byte,b) renderAtt (Hspace_Att_31 b) = (hspace_byte,b) renderAtt (Vspace_Att_31 b) = (vspace_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 (Size_Att_30 b) = (size_byte,b) renderAtt (Color_Att_30 b) = (color_byte,b) renderAtt (Face_Att_30 b) = (face_byte,b) instance RenderAttribute Att29 where renderAtt (Size_Att_29 b) = (size_byte,b) instance RenderAttribute Att28 where renderAtt (Id_Att_28 b) = (id_byte,b) renderAtt (Size_Att_28 b) = (size_byte,b) renderAtt (Color_Att_28 b) = (color_byte,b) renderAtt (Face_Att_28 b) = (face_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 (Clear_Att_27 b) = (clear_byte,b) instance RenderAttribute Att26 where renderAtt (Dir_Att_26 b) = (dir_byte,b) instance RenderAttribute Att25 where 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 (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 (Lang_Att_25 b) = (lang_byte,b) renderAtt (Dir_Att_25 b) = (dir_byte,b) instance RenderAttribute Att24 where renderAtt (Id_Att_24 b) = (id_byte,b) renderAtt (Class_Att_24 b) = (class_byte,b) renderAtt (Style_Att_24 b) = (style_byte,b) renderAtt (Title_Att_24 b) = (title_byte,b) renderAtt (Lang_Att_24 b) = (lang_byte,b) renderAtt (Dir_Att_24 b) = (dir_byte,b) renderAtt (Onclick_Att_24 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_24 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_24 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_24 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_24 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_24 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_24 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_24 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_24 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_24 b) = (onkeyup_byte,b) renderAtt (Accesskey_Att_24 b) = (accesskey_byte,b) renderAtt (Tabindex_Att_24 b) = (tabindex_byte,b) renderAtt (Onfocus_Att_24 b) = (onfocus_byte,b) renderAtt (Onblur_Att_24 b) = (onblur_byte,b) renderAtt (Charset_Att_24 b) = (charset_byte,b) renderAtt (Type_Att_24 b) = (type_byte,b) renderAtt (Name_Att_24 b) = (name_byte,b) renderAtt (Href_Att_24 b) = (href_byte,b) renderAtt (Hreflang_Att_24 b) = (hreflang_byte,b) renderAtt (Rel_Att_24 b) = (rel_byte,b) renderAtt (Rev_Att_24 b) = (rev_byte,b) renderAtt (Shape_Att_24 b) = (shape_byte,b) renderAtt (Coords_Att_24 b) = (coords_byte,b) renderAtt (Target_Att_24 b) = (target_byte,b) instance RenderAttribute Att23 where renderAtt (Id_Att_23 b) = (id_byte,b) renderAtt (Class_Att_23 b) = (class_byte,b) renderAtt (Style_Att_23 b) = (style_byte,b) renderAtt (Title_Att_23 b) = (title_byte,b) renderAtt (Lang_Att_23 b) = (lang_byte,b) renderAtt (Dir_Att_23 b) = (dir_byte,b) renderAtt (Onclick_Att_23 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_23 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_23 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_23 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_23 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_23 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_23 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_23 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_23 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_23 b) = (onkeyup_byte,b) renderAtt (Cite_Att_23 b) = (cite_byte,b) renderAtt (Datetime_Att_23 b) = (datetime_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 (Cite_Att_22 b) = (cite_byte,b) instance RenderAttribute Att21 where renderAtt (Id_Att_21 b) = (id_byte,b) renderAtt (Class_Att_21 b) = (class_byte,b) renderAtt (Style_Att_21 b) = (style_byte,b) renderAtt (Title_Att_21 b) = (title_byte,b) renderAtt (Lang_Att_21 b) = (lang_byte,b) renderAtt (Dir_Att_21 b) = (dir_byte,b) renderAtt (Onclick_Att_21 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_21 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_21 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_21 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_21 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_21 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_21 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_21 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_21 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_21 b) = (onkeyup_byte,b) renderAtt (Width_Att_21 b) = (width_byte,b) renderAtt (Space_Att_21 b) = (space_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 (Align_Att_20 b) = (align_byte,b) renderAtt (Noshade_Att_20 b) = (noshade_byte,b) renderAtt (Size_Att_20 b) = (size_byte,b) renderAtt (Width_Att_20 b) = (width_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) renderAtt (Lang_Att_19 b) = (lang_byte,b) renderAtt (Dir_Att_19 b) = (dir_byte,b) renderAtt (Onclick_Att_19 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_19 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_19 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_19 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_19 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_19 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_19 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_19 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_19 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_19 b) = (onkeyup_byte,b) renderAtt (Type_Att_19 b) = (type_byte,b) renderAtt (Value_Att_19 b) = (value_byte,b) instance RenderAttribute Att18 where renderAtt (Id_Att_18 b) = (id_byte,b) renderAtt (Class_Att_18 b) = (class_byte,b) renderAtt (Style_Att_18 b) = (style_byte,b) renderAtt (Title_Att_18 b) = (title_byte,b) renderAtt (Lang_Att_18 b) = (lang_byte,b) renderAtt (Dir_Att_18 b) = (dir_byte,b) renderAtt (Onclick_Att_18 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_18 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_18 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_18 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_18 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_18 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_18 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_18 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_18 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_18 b) = (onkeyup_byte,b) renderAtt (Compact_Att_18 b) = (compact_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 (Lang_Att_17 b) = (lang_byte,b) renderAtt (Dir_Att_17 b) = (dir_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 (Type_Att_17 b) = (type_byte,b) renderAtt (Compact_Att_17 b) = (compact_byte,b) renderAtt (Start_Att_17 b) = (start_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 (Type_Att_16 b) = (type_byte,b) renderAtt (Compact_Att_16 b) = (compact_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 (Align_Att_15 b) = (align_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 (Onload_Att_14 b) = (onload_byte,b) renderAtt (Onunload_Att_14 b) = (onunload_byte,b) renderAtt (Background_Att_14 b) = (background_byte,b) renderAtt (Bgcolor_Att_14 b) = (bgcolor_byte,b) renderAtt (Text_Att_14 b) = (text_byte,b) renderAtt (Link_Att_14 b) = (link_byte,b) renderAtt (Vlink_Att_14 b) = (vlink_byte,b) renderAtt (Alink_Att_14 b) = (alink_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 (Longdesc_Att_13 b) = (longdesc_byte,b) renderAtt (Name_Att_13 b) = (name_byte,b) renderAtt (Src_Att_13 b) = (src_byte,b) renderAtt (Frameborder_Att_13 b) = (frameborder_byte,b) renderAtt (Marginwidth_Att_13 b) = (marginwidth_byte,b) renderAtt (Marginheight_Att_13 b) = (marginheight_byte,b) renderAtt (Scrolling_Att_13 b) = (scrolling_byte,b) renderAtt (Align_Att_13 b) = (align_byte,b) renderAtt (Height_Att_13 b) = (height_byte,b) renderAtt (Width_Att_13 b) = (width_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 (Longdesc_Att_12 b) = (longdesc_byte,b) renderAtt (Name_Att_12 b) = (name_byte,b) renderAtt (Src_Att_12 b) = (src_byte,b) renderAtt (Frameborder_Att_12 b) = (frameborder_byte,b) renderAtt (Marginwidth_Att_12 b) = (marginwidth_byte,b) renderAtt (Marginheight_Att_12 b) = (marginheight_byte,b) renderAtt (Noresize_Att_12 b) = (noresize_byte,b) renderAtt (Scrolling_Att_12 b) = (scrolling_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 (Rows_Att_11 b) = (rows_byte,b) renderAtt (Cols_Att_11 b) = (cols_byte,b) renderAtt (Onload_Att_11 b) = (onload_byte,b) renderAtt (Onunload_Att_11 b) = (onunload_byte,b) instance RenderAttribute Att10 where renderAtt (Id_Att_10 b) = (id_byte,b) renderAtt (Class_Att_10 b) = (class_byte,b) renderAtt (Style_Att_10 b) = (style_byte,b) renderAtt (Title_Att_10 b) = (title_byte,b) renderAtt (Lang_Att_10 b) = (lang_byte,b) renderAtt (Dir_Att_10 b) = (dir_byte,b) renderAtt (Onclick_Att_10 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_10 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_10 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_10 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_10 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_10 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_10 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_10 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_10 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_10 b) = (onkeyup_byte,b) instance RenderAttribute Att9 where renderAtt (Id_Att_9 b) = (id_byte,b) renderAtt (Charset_Att_9 b) = (charset_byte,b) renderAtt (Type_Att_9 b) = (type_byte,b) renderAtt (Language_Att_9 b) = (language_byte,b) renderAtt (Src_Att_9 b) = (src_byte,b) renderAtt (Defer_Att_9 b) = (defer_byte,b) renderAtt (Space_Att_9 b) = (space_byte,b) instance RenderAttribute Att8 where renderAtt (Type_Att_8 b) = (type_byte,b) instance RenderAttribute Att7 where renderAtt (Lang_Att_7 b) = (lang_byte,b) renderAtt (Dir_Att_7 b) = (dir_byte,b) renderAtt (Id_Att_7 b) = (id_byte,b) renderAtt (Type_Att_7 b) = (type_byte,b) renderAtt (Media_Att_7 b) = (media_byte,b) renderAtt (Title_Att_7 b) = (title_byte,b) renderAtt (Space_Att_7 b) = (space_byte,b) instance RenderAttribute Att6 where renderAtt (Id_Att_6 b) = (id_byte,b) renderAtt (Class_Att_6 b) = (class_byte,b) renderAtt (Style_Att_6 b) = (style_byte,b) renderAtt (Title_Att_6 b) = (title_byte,b) renderAtt (Lang_Att_6 b) = (lang_byte,b) renderAtt (Dir_Att_6 b) = (dir_byte,b) renderAtt (Onclick_Att_6 b) = (onclick_byte,b) renderAtt (Ondblclick_Att_6 b) = (ondblclick_byte,b) renderAtt (Onmousedown_Att_6 b) = (onmousedown_byte,b) renderAtt (Onmouseup_Att_6 b) = (onmouseup_byte,b) renderAtt (Onmouseover_Att_6 b) = (onmouseover_byte,b) renderAtt (Onmousemove_Att_6 b) = (onmousemove_byte,b) renderAtt (Onmouseout_Att_6 b) = (onmouseout_byte,b) renderAtt (Onkeypress_Att_6 b) = (onkeypress_byte,b) renderAtt (Onkeydown_Att_6 b) = (onkeydown_byte,b) renderAtt (Onkeyup_Att_6 b) = (onkeyup_byte,b) renderAtt (Charset_Att_6 b) = (charset_byte,b) renderAtt (Href_Att_6 b) = (href_byte,b) renderAtt (Hreflang_Att_6 b) = (hreflang_byte,b) renderAtt (Type_Att_6 b) = (type_byte,b) renderAtt (Rel_Att_6 b) = (rel_byte,b) renderAtt (Rev_Att_6 b) = (rev_byte,b) renderAtt (Media_Att_6 b) = (media_byte,b) renderAtt (Target_Att_6 b) = (target_byte,b) instance RenderAttribute Att5 where renderAtt (Content_Att_5 b) = (content_byte,b) instance RenderAttribute Att4 where renderAtt (Lang_Att_4 b) = (lang_byte,b) renderAtt (Dir_Att_4 b) = (dir_byte,b) renderAtt (Id_Att_4 b) = (id_byte,b) renderAtt (Http_equiv_Att_4 b) = (http_equiv_byte,b) renderAtt (Name_Att_4 b) = (name_byte,b) renderAtt (Content_Att_4 b) = (content_byte,b) renderAtt (Scheme_Att_4 b) = (scheme_byte,b) instance RenderAttribute Att3 where renderAtt (Id_Att_3 b) = (id_byte,b) renderAtt (Href_Att_3 b) = (href_byte,b) renderAtt (Target_Att_3 b) = (target_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] | Frameset_0 [Att11] [Ent50] deriving (Show) data Ent1 = Title_1 [Att2] [Ent2] | Base_1 [Att3] | Meta_1 [Att4] | Link_1 [Att6] | Style_1 [Att7] [Ent2] | Script_1 [Att9] [Ent2] | Object_1 [Att31] [Ent3] | Isindex_1 [Att56] deriving (Show) data Ent2 = PCDATA_2 [Att0] B.ByteString deriving (Show) data Ent3 = Script_3 [Att9] [Ent2] | Noscript_3 [Att10] [Ent4] | Iframe_3 [Att13] [Ent4] | Div_3 [Att15] [Ent4] | P_3 [Att15] [Ent5] | H1_3 [Att15] [Ent5] | H2_3 [Att15] [Ent5] | H3_3 [Att15] [Ent5] | H4_3 [Att15] [Ent5] | H5_3 [Att15] [Ent5] | H6_3 [Att15] [Ent5] | Ul_3 [Att16] [Ent6] | Ol_3 [Att17] [Ent6] | Menu_3 [Att18] [Ent6] | Dir_3 [Att18] [Ent6] | Dl_3 [Att18] [Ent7] | Address_3 [Att10] [Ent8] | Hr_3 [Att20] | Pre_3 [Att21] [Ent9] | Blockquote_3 [Att22] [Ent4] | Center_3 [Att10] [Ent4] | Ins_3 [Att23] [Ent4] | Del_3 [Att23] [Ent4] | A_3 [Att24] [Ent10] | Span_3 [Att10] [Ent5] | Bdo_3 [Att10] [Ent5] | Br_3 [Att27] | Em_3 [Att10] [Ent5] | Strong_3 [Att10] [Ent5] | Dfn_3 [Att10] [Ent5] | Code_3 [Att10] [Ent5] | Samp_3 [Att10] [Ent5] | Kbd_3 [Att10] [Ent5] | Var_3 [Att10] [Ent5] | Cite_3 [Att10] [Ent5] | Abbr_3 [Att10] [Ent5] | Acronym_3 [Att10] [Ent5] | Q_3 [Att22] [Ent5] | Sub_3 [Att10] [Ent5] | Sup_3 [Att10] [Ent5] | Tt_3 [Att10] [Ent5] | I_3 [Att10] [Ent5] | B_3 [Att10] [Ent5] | Big_3 [Att10] [Ent5] | Small_3 [Att10] [Ent5] | U_3 [Att10] [Ent5] | S_3 [Att10] [Ent5] | Strike_3 [Att10] [Ent5] | Basefont_3 [Att28] | Font_3 [Att30] [Ent5] | Object_3 [Att31] [Ent3] | Param_3 [Att32] | Applet_3 [Att34] [Ent3] | Img_3 [Att37] | Map_3 [Att40] [Ent22] | Form_3 [Att43] [Ent34] | Label_3 [Att45] [Ent39] | Input_3 [Att46] | Select_3 [Att47] [Ent31] | Textarea_3 [Att51] [Ent2] | Fieldset_3 [Att10] [Ent49] | Button_3 [Att55] [Ent33] | Isindex_3 [Att56] | Table_3 [Att57] [Ent16] | PCDATA_3 [Att0] B.ByteString deriving (Show) data Ent4 = Script_4 [Att9] [Ent2] | Noscript_4 [Att10] [Ent4] | Iframe_4 [Att13] [Ent4] | Div_4 [Att15] [Ent4] | P_4 [Att15] [Ent5] | H1_4 [Att15] [Ent5] | H2_4 [Att15] [Ent5] | H3_4 [Att15] [Ent5] | H4_4 [Att15] [Ent5] | H5_4 [Att15] [Ent5] | H6_4 [Att15] [Ent5] | Ul_4 [Att16] [Ent6] | Ol_4 [Att17] [Ent6] | Menu_4 [Att18] [Ent6] | Dir_4 [Att18] [Ent6] | Dl_4 [Att18] [Ent7] | Address_4 [Att10] [Ent8] | Hr_4 [Att20] | Pre_4 [Att21] [Ent9] | Blockquote_4 [Att22] [Ent4] | Center_4 [Att10] [Ent4] | Ins_4 [Att23] [Ent4] | Del_4 [Att23] [Ent4] | A_4 [Att24] [Ent10] | Span_4 [Att10] [Ent5] | Bdo_4 [Att10] [Ent5] | Br_4 [Att27] | Em_4 [Att10] [Ent5] | Strong_4 [Att10] [Ent5] | Dfn_4 [Att10] [Ent5] | Code_4 [Att10] [Ent5] | Samp_4 [Att10] [Ent5] | Kbd_4 [Att10] [Ent5] | Var_4 [Att10] [Ent5] | Cite_4 [Att10] [Ent5] | Abbr_4 [Att10] [Ent5] | Acronym_4 [Att10] [Ent5] | Q_4 [Att22] [Ent5] | Sub_4 [Att10] [Ent5] | Sup_4 [Att10] [Ent5] | Tt_4 [Att10] [Ent5] | I_4 [Att10] [Ent5] | B_4 [Att10] [Ent5] | Big_4 [Att10] [Ent5] | Small_4 [Att10] [Ent5] | U_4 [Att10] [Ent5] | S_4 [Att10] [Ent5] | Strike_4 [Att10] [Ent5] | Basefont_4 [Att28] | Font_4 [Att30] [Ent5] | Object_4 [Att31] [Ent3] | Applet_4 [Att34] [Ent3] | Img_4 [Att37] | Map_4 [Att40] [Ent22] | Form_4 [Att43] [Ent34] | Label_4 [Att45] [Ent39] | Input_4 [Att46] | Select_4 [Att47] [Ent31] | Textarea_4 [Att51] [Ent2] | Fieldset_4 [Att10] [Ent49] | Button_4 [Att55] [Ent33] | Isindex_4 [Att56] | Table_4 [Att57] [Ent16] | PCDATA_4 [Att0] B.ByteString deriving (Show) data Ent5 = Script_5 [Att9] [Ent2] | Iframe_5 [Att13] [Ent4] | Ins_5 [Att23] [Ent4] | Del_5 [Att23] [Ent4] | A_5 [Att24] [Ent10] | Span_5 [Att10] [Ent5] | Bdo_5 [Att10] [Ent5] | Br_5 [Att27] | Em_5 [Att10] [Ent5] | Strong_5 [Att10] [Ent5] | Dfn_5 [Att10] [Ent5] | Code_5 [Att10] [Ent5] | Samp_5 [Att10] [Ent5] | Kbd_5 [Att10] [Ent5] | Var_5 [Att10] [Ent5] | Cite_5 [Att10] [Ent5] | Abbr_5 [Att10] [Ent5] | Acronym_5 [Att10] [Ent5] | Q_5 [Att22] [Ent5] | Sub_5 [Att10] [Ent5] | Sup_5 [Att10] [Ent5] | Tt_5 [Att10] [Ent5] | I_5 [Att10] [Ent5] | B_5 [Att10] [Ent5] | Big_5 [Att10] [Ent5] | Small_5 [Att10] [Ent5] | U_5 [Att10] [Ent5] | S_5 [Att10] [Ent5] | Strike_5 [Att10] [Ent5] | Basefont_5 [Att28] | Font_5 [Att30] [Ent5] | Object_5 [Att31] [Ent3] | Applet_5 [Att34] [Ent3] | Img_5 [Att37] | Map_5 [Att40] [Ent22] | Label_5 [Att45] [Ent39] | Input_5 [Att46] | Select_5 [Att47] [Ent31] | Textarea_5 [Att51] [Ent2] | Button_5 [Att55] [Ent33] | PCDATA_5 [Att0] B.ByteString deriving (Show) data Ent6 = Li_6 [Att19] [Ent4] deriving (Show) data Ent7 = Dt_7 [Att10] [Ent5] | Dd_7 [Att10] [Ent4] deriving (Show) data Ent8 = Script_8 [Att9] [Ent2] | Iframe_8 [Att13] [Ent4] | P_8 [Att15] [Ent5] | Ins_8 [Att23] [Ent4] | Del_8 [Att23] [Ent4] | A_8 [Att24] [Ent10] | Span_8 [Att10] [Ent5] | Bdo_8 [Att10] [Ent5] | Br_8 [Att27] | Em_8 [Att10] [Ent5] | Strong_8 [Att10] [Ent5] | Dfn_8 [Att10] [Ent5] | Code_8 [Att10] [Ent5] | Samp_8 [Att10] [Ent5] | Kbd_8 [Att10] [Ent5] | Var_8 [Att10] [Ent5] | Cite_8 [Att10] [Ent5] | Abbr_8 [Att10] [Ent5] | Acronym_8 [Att10] [Ent5] | Q_8 [Att22] [Ent5] | Sub_8 [Att10] [Ent5] | Sup_8 [Att10] [Ent5] | Tt_8 [Att10] [Ent5] | I_8 [Att10] [Ent5] | B_8 [Att10] [Ent5] | Big_8 [Att10] [Ent5] | Small_8 [Att10] [Ent5] | U_8 [Att10] [Ent5] | S_8 [Att10] [Ent5] | Strike_8 [Att10] [Ent5] | Basefont_8 [Att28] | Font_8 [Att30] [Ent5] | Object_8 [Att31] [Ent3] | Applet_8 [Att34] [Ent3] | Img_8 [Att37] | Map_8 [Att40] [Ent22] | Label_8 [Att45] [Ent39] | Input_8 [Att46] | Select_8 [Att47] [Ent31] | Textarea_8 [Att51] [Ent2] | Button_8 [Att55] [Ent33] | PCDATA_8 [Att0] B.ByteString deriving (Show) data Ent9 = Script_9 [Att9] [Ent2] | Ins_9 [Att23] [Ent4] | Del_9 [Att23] [Ent4] | A_9 [Att24] [Ent10] | Span_9 [Att10] [Ent5] | Bdo_9 [Att10] [Ent5] | Br_9 [Att27] | Em_9 [Att10] [Ent5] | Strong_9 [Att10] [Ent5] | Dfn_9 [Att10] [Ent5] | Code_9 [Att10] [Ent5] | Samp_9 [Att10] [Ent5] | Kbd_9 [Att10] [Ent5] | Var_9 [Att10] [Ent5] | Cite_9 [Att10] [Ent5] | Abbr_9 [Att10] [Ent5] | Acronym_9 [Att10] [Ent5] | Q_9 [Att22] [Ent5] | Tt_9 [Att10] [Ent5] | I_9 [Att10] [Ent5] | B_9 [Att10] [Ent5] | U_9 [Att10] [Ent5] | S_9 [Att10] [Ent5] | Strike_9 [Att10] [Ent5] | Label_9 [Att45] [Ent39] | Input_9 [Att46] | Select_9 [Att47] [Ent31] | Textarea_9 [Att51] [Ent2] | Button_9 [Att55] [Ent33] | PCDATA_9 [Att0] B.ByteString deriving (Show) data Ent10 = Script_10 [Att9] [Ent2] | Iframe_10 [Att13] [Ent11] | Ins_10 [Att23] [Ent11] | Del_10 [Att23] [Ent11] | Span_10 [Att10] [Ent10] | Bdo_10 [Att10] [Ent10] | Br_10 [Att27] | Em_10 [Att10] [Ent10] | Strong_10 [Att10] [Ent10] | Dfn_10 [Att10] [Ent10] | Code_10 [Att10] [Ent10] | Samp_10 [Att10] [Ent10] | Kbd_10 [Att10] [Ent10] | Var_10 [Att10] [Ent10] | Cite_10 [Att10] [Ent10] | Abbr_10 [Att10] [Ent10] | Acronym_10 [Att10] [Ent10] | Q_10 [Att22] [Ent10] | Sub_10 [Att10] [Ent10] | Sup_10 [Att10] [Ent10] | Tt_10 [Att10] [Ent10] | I_10 [Att10] [Ent10] | B_10 [Att10] [Ent10] | Big_10 [Att10] [Ent10] | Small_10 [Att10] [Ent10] | U_10 [Att10] [Ent10] | S_10 [Att10] [Ent10] | Strike_10 [Att10] [Ent10] | Basefont_10 [Att28] | Font_10 [Att30] [Ent10] | Object_10 [Att31] [Ent21] | Applet_10 [Att34] [Ent21] | Img_10 [Att37] | Map_10 [Att40] [Ent22] | Label_10 [Att45] [Ent23] | Input_10 [Att46] | Select_10 [Att47] [Ent31] | Textarea_10 [Att51] [Ent2] | Button_10 [Att55] [Ent33] | PCDATA_10 [Att0] B.ByteString deriving (Show) data Ent11 = Script_11 [Att9] [Ent2] | Noscript_11 [Att10] [Ent11] | Iframe_11 [Att13] [Ent11] | Div_11 [Att15] [Ent11] | P_11 [Att15] [Ent10] | H1_11 [Att15] [Ent10] | H2_11 [Att15] [Ent10] | H3_11 [Att15] [Ent10] | H4_11 [Att15] [Ent10] | H5_11 [Att15] [Ent10] | H6_11 [Att15] [Ent10] | Ul_11 [Att16] [Ent6] | Ol_11 [Att17] [Ent6] | Menu_11 [Att18] [Ent6] | Dir_11 [Att18] [Ent6] | Dl_11 [Att18] [Ent7] | Address_11 [Att10] [Ent12] | Hr_11 [Att20] | Pre_11 [Att21] [Ent13] | Blockquote_11 [Att22] [Ent11] | Center_11 [Att10] [Ent11] | Ins_11 [Att23] [Ent11] | Del_11 [Att23] [Ent11] | Span_11 [Att10] [Ent10] | Bdo_11 [Att10] [Ent10] | Br_11 [Att27] | Em_11 [Att10] [Ent10] | Strong_11 [Att10] [Ent10] | Dfn_11 [Att10] [Ent10] | Code_11 [Att10] [Ent10] | Samp_11 [Att10] [Ent10] | Kbd_11 [Att10] [Ent10] | Var_11 [Att10] [Ent10] | Cite_11 [Att10] [Ent10] | Abbr_11 [Att10] [Ent10] | Acronym_11 [Att10] [Ent10] | Q_11 [Att22] [Ent10] | Sub_11 [Att10] [Ent10] | Sup_11 [Att10] [Ent10] | Tt_11 [Att10] [Ent10] | I_11 [Att10] [Ent10] | B_11 [Att10] [Ent10] | Big_11 [Att10] [Ent10] | Small_11 [Att10] [Ent10] | U_11 [Att10] [Ent10] | S_11 [Att10] [Ent10] | Strike_11 [Att10] [Ent10] | Basefont_11 [Att28] | Font_11 [Att30] [Ent10] | Object_11 [Att31] [Ent21] | Applet_11 [Att34] [Ent21] | Img_11 [Att37] | Map_11 [Att40] [Ent22] | Form_11 [Att43] [Ent14] | Label_11 [Att45] [Ent23] | Input_11 [Att46] | Select_11 [Att47] [Ent31] | Textarea_11 [Att51] [Ent2] | Fieldset_11 [Att10] [Ent20] | Button_11 [Att55] [Ent33] | Isindex_11 [Att56] | Table_11 [Att57] [Ent16] | PCDATA_11 [Att0] B.ByteString deriving (Show) data Ent12 = Script_12 [Att9] [Ent2] | Iframe_12 [Att13] [Ent11] | P_12 [Att15] [Ent10] | Ins_12 [Att23] [Ent11] | Del_12 [Att23] [Ent11] | Span_12 [Att10] [Ent10] | Bdo_12 [Att10] [Ent10] | Br_12 [Att27] | Em_12 [Att10] [Ent10] | Strong_12 [Att10] [Ent10] | Dfn_12 [Att10] [Ent10] | Code_12 [Att10] [Ent10] | Samp_12 [Att10] [Ent10] | Kbd_12 [Att10] [Ent10] | Var_12 [Att10] [Ent10] | Cite_12 [Att10] [Ent10] | Abbr_12 [Att10] [Ent10] | Acronym_12 [Att10] [Ent10] | Q_12 [Att22] [Ent10] | Sub_12 [Att10] [Ent10] | Sup_12 [Att10] [Ent10] | Tt_12 [Att10] [Ent10] | I_12 [Att10] [Ent10] | B_12 [Att10] [Ent10] | Big_12 [Att10] [Ent10] | Small_12 [Att10] [Ent10] | U_12 [Att10] [Ent10] | S_12 [Att10] [Ent10] | Strike_12 [Att10] [Ent10] | Basefont_12 [Att28] | Font_12 [Att30] [Ent10] | Object_12 [Att31] [Ent21] | Applet_12 [Att34] [Ent21] | Img_12 [Att37] | Map_12 [Att40] [Ent22] | Label_12 [Att45] [Ent23] | Input_12 [Att46] | Select_12 [Att47] [Ent31] | Textarea_12 [Att51] [Ent2] | Button_12 [Att55] [Ent33] | PCDATA_12 [Att0] B.ByteString deriving (Show) data Ent13 = Script_13 [Att9] [Ent2] | Ins_13 [Att23] [Ent11] | Del_13 [Att23] [Ent11] | Span_13 [Att10] [Ent10] | Bdo_13 [Att10] [Ent10] | Br_13 [Att27] | Em_13 [Att10] [Ent10] | Strong_13 [Att10] [Ent10] | Dfn_13 [Att10] [Ent10] | Code_13 [Att10] [Ent10] | Samp_13 [Att10] [Ent10] | Kbd_13 [Att10] [Ent10] | Var_13 [Att10] [Ent10] | Cite_13 [Att10] [Ent10] | Abbr_13 [Att10] [Ent10] | Acronym_13 [Att10] [Ent10] | Q_13 [Att22] [Ent10] | Tt_13 [Att10] [Ent10] | I_13 [Att10] [Ent10] | B_13 [Att10] [Ent10] | U_13 [Att10] [Ent10] | S_13 [Att10] [Ent10] | Strike_13 [Att10] [Ent10] | Label_13 [Att45] [Ent23] | Input_13 [Att46] | Select_13 [Att47] [Ent31] | Textarea_13 [Att51] [Ent2] | Button_13 [Att55] [Ent33] | PCDATA_13 [Att0] B.ByteString deriving (Show) data Ent14 = Script_14 [Att9] [Ent2] | Noscript_14 [Att10] [Ent14] | Iframe_14 [Att13] [Ent14] | Div_14 [Att15] [Ent14] | P_14 [Att15] [Ent10] | H1_14 [Att15] [Ent10] | H2_14 [Att15] [Ent10] | H3_14 [Att15] [Ent10] | H4_14 [Att15] [Ent10] | H5_14 [Att15] [Ent10] | H6_14 [Att15] [Ent10] | Ul_14 [Att16] [Ent6] | Ol_14 [Att17] [Ent6] | Menu_14 [Att18] [Ent2] | Dir_14 [Att18] [Ent6] | Dl_14 [Att18] [Ent7] | Address_14 [Att10] [Ent12] | Hr_14 [Att20] | Pre_14 [Att21] [Ent13] | Blockquote_14 [Att22] [Ent14] | Center_14 [Att10] [Ent14] | Ins_14 [Att23] [Ent14] | Del_14 [Att23] [Ent14] | Span_14 [Att10] [Ent10] | Bdo_14 [Att10] [Ent10] | Br_14 [Att27] | Em_14 [Att10] [Ent10] | Strong_14 [Att10] [Ent10] | Dfn_14 [Att10] [Ent10] | Code_14 [Att10] [Ent10] | Samp_14 [Att10] [Ent10] | Kbd_14 [Att10] [Ent10] | Var_14 [Att10] [Ent10] | Cite_14 [Att10] [Ent10] | Abbr_14 [Att10] [Ent10] | Acronym_14 [Att10] [Ent10] | Q_14 [Att22] [Ent10] | Sub_14 [Att10] [Ent10] | Sup_14 [Att10] [Ent10] | Tt_14 [Att10] [Ent10] | I_14 [Att10] [Ent10] | B_14 [Att10] [Ent10] | Big_14 [Att10] [Ent10] | Small_14 [Att10] [Ent10] | U_14 [Att10] [Ent10] | S_14 [Att10] [Ent10] | Strike_14 [Att10] [Ent10] | Basefont_14 [Att28] | Font_14 [Att30] [Ent10] | Object_14 [Att31] [Ent35] | Applet_14 [Att34] [Ent35] | Img_14 [Att37] | Map_14 [Att40] [Ent36] | Label_14 [Att45] [Ent23] | Input_14 [Att46] | Select_14 [Att47] [Ent31] | Textarea_14 [Att51] [Ent2] | Fieldset_14 [Att10] [Ent15] | Button_14 [Att55] [Ent33] | Isindex_14 [Att56] | Table_14 [Att57] [Ent16] | PCDATA_14 [Att0] B.ByteString deriving (Show) data Ent15 = Script_15 [Att9] [Ent2] | Noscript_15 [Att10] [Ent14] | Iframe_15 [Att13] [Ent14] | Div_15 [Att15] [Ent14] | P_15 [Att15] [Ent10] | H1_15 [Att15] [Ent10] | H2_15 [Att15] [Ent10] | H3_15 [Att15] [Ent10] | H4_15 [Att15] [Ent10] | H5_15 [Att15] [Ent10] | H6_15 [Att15] [Ent10] | Ul_15 [Att16] [Ent6] | Ol_15 [Att17] [Ent6] | Menu_15 [Att18] [Ent2] | Dir_15 [Att18] [Ent6] | Dl_15 [Att18] [Ent7] | Address_15 [Att10] [Ent12] | Hr_15 [Att20] | Pre_15 [Att21] [Ent13] | Blockquote_15 [Att22] [Ent14] | Center_15 [Att10] [Ent14] | Ins_15 [Att23] [Ent14] | Del_15 [Att23] [Ent14] | Span_15 [Att10] [Ent10] | Bdo_15 [Att10] [Ent10] | Br_15 [Att27] | Em_15 [Att10] [Ent10] | Strong_15 [Att10] [Ent10] | Dfn_15 [Att10] [Ent10] | Code_15 [Att10] [Ent10] | Samp_15 [Att10] [Ent10] | Kbd_15 [Att10] [Ent10] | Var_15 [Att10] [Ent10] | Cite_15 [Att10] [Ent10] | Abbr_15 [Att10] [Ent10] | Acronym_15 [Att10] [Ent10] | Q_15 [Att22] [Ent10] | Sub_15 [Att10] [Ent10] | Sup_15 [Att10] [Ent10] | Tt_15 [Att10] [Ent10] | I_15 [Att10] [Ent10] | B_15 [Att10] [Ent10] | Big_15 [Att10] [Ent10] | Small_15 [Att10] [Ent10] | U_15 [Att10] [Ent10] | S_15 [Att10] [Ent10] | Strike_15 [Att10] [Ent10] | Basefont_15 [Att28] | Font_15 [Att30] [Ent10] | Object_15 [Att31] [Ent35] | Applet_15 [Att34] [Ent35] | Img_15 [Att37] | Map_15 [Att40] [Ent36] | Label_15 [Att45] [Ent23] | Input_15 [Att46] | Select_15 [Att47] [Ent31] | Textarea_15 [Att51] [Ent2] | Fieldset_15 [Att10] [Ent15] | Legend_15 [Att54] [Ent10] | Button_15 [Att55] [Ent33] | Isindex_15 [Att56] | Table_15 [Att57] [Ent16] | PCDATA_15 [Att0] B.ByteString deriving (Show) data Ent16 = Caption_16 [Att15] [Ent10] | Thead_16 [Att58] [Ent17] | Tfoot_16 [Att58] [Ent17] | Tbody_16 [Att58] [Ent17] | Colgroup_16 [Att59] [Ent18] | Col_16 [Att59] | Tr_16 [Att60] [Ent19] deriving (Show) data Ent17 = Tr_17 [Att60] [Ent19] deriving (Show) data Ent18 = Col_18 [Att59] deriving (Show) data Ent19 = Th_19 [Att61] [Ent14] | Td_19 [Att61] [Ent14] deriving (Show) data Ent20 = Script_20 [Att9] [Ent2] | Noscript_20 [Att10] [Ent11] | Iframe_20 [Att13] [Ent11] | Div_20 [Att15] [Ent11] | P_20 [Att15] [Ent10] | H1_20 [Att15] [Ent10] | H2_20 [Att15] [Ent10] | H3_20 [Att15] [Ent10] | H4_20 [Att15] [Ent10] | H5_20 [Att15] [Ent10] | H6_20 [Att15] [Ent10] | Ul_20 [Att16] [Ent6] | Ol_20 [Att17] [Ent6] | Menu_20 [Att18] [Ent6] | Dir_20 [Att18] [Ent6] | Dl_20 [Att18] [Ent7] | Address_20 [Att10] [Ent12] | Hr_20 [Att20] | Pre_20 [Att21] [Ent13] | Blockquote_20 [Att22] [Ent11] | Center_20 [Att10] [Ent11] | Ins_20 [Att23] [Ent11] | Del_20 [Att23] [Ent11] | Span_20 [Att10] [Ent10] | Bdo_20 [Att10] [Ent10] | Br_20 [Att27] | Em_20 [Att10] [Ent10] | Strong_20 [Att10] [Ent10] | Dfn_20 [Att10] [Ent10] | Code_20 [Att10] [Ent10] | Samp_20 [Att10] [Ent10] | Kbd_20 [Att10] [Ent10] | Var_20 [Att10] [Ent10] | Cite_20 [Att10] [Ent10] | Abbr_20 [Att10] [Ent10] | Acronym_20 [Att10] [Ent10] | Q_20 [Att22] [Ent10] | Sub_20 [Att10] [Ent10] | Sup_20 [Att10] [Ent10] | Tt_20 [Att10] [Ent10] | I_20 [Att10] [Ent10] | B_20 [Att10] [Ent10] | Big_20 [Att10] [Ent10] | Small_20 [Att10] [Ent10] | U_20 [Att10] [Ent10] | S_20 [Att10] [Ent10] | Strike_20 [Att10] [Ent10] | Basefont_20 [Att28] | Font_20 [Att30] [Ent10] | Object_20 [Att31] [Ent21] | Applet_20 [Att34] [Ent21] | Img_20 [Att37] | Map_20 [Att40] [Ent22] | Form_20 [Att43] [Ent14] | Label_20 [Att45] [Ent23] | Input_20 [Att46] | Select_20 [Att47] [Ent31] | Textarea_20 [Att51] [Ent2] | Fieldset_20 [Att10] [Ent20] | Legend_20 [Att54] [Ent10] | Button_20 [Att55] [Ent33] | Isindex_20 [Att56] | Table_20 [Att57] [Ent16] | PCDATA_20 [Att0] B.ByteString deriving (Show) data Ent21 = Script_21 [Att9] [Ent2] | Noscript_21 [Att10] [Ent11] | Iframe_21 [Att13] [Ent11] | Div_21 [Att15] [Ent11] | P_21 [Att15] [Ent10] | H1_21 [Att15] [Ent10] | H2_21 [Att15] [Ent10] | H3_21 [Att15] [Ent10] | H4_21 [Att15] [Ent10] | H5_21 [Att15] [Ent10] | H6_21 [Att15] [Ent10] | Ul_21 [Att16] [Ent6] | Ol_21 [Att17] [Ent6] | Menu_21 [Att18] [Ent6] | Dir_21 [Att18] [Ent6] | Dl_21 [Att18] [Ent7] | Address_21 [Att10] [Ent12] | Hr_21 [Att20] | Pre_21 [Att21] [Ent13] | Blockquote_21 [Att22] [Ent11] | Center_21 [Att10] [Ent11] | Ins_21 [Att23] [Ent11] | Del_21 [Att23] [Ent11] | Span_21 [Att10] [Ent10] | Bdo_21 [Att10] [Ent10] | Br_21 [Att27] | Em_21 [Att10] [Ent10] | Strong_21 [Att10] [Ent10] | Dfn_21 [Att10] [Ent10] | Code_21 [Att10] [Ent10] | Samp_21 [Att10] [Ent10] | Kbd_21 [Att10] [Ent10] | Var_21 [Att10] [Ent10] | Cite_21 [Att10] [Ent10] | Abbr_21 [Att10] [Ent10] | Acronym_21 [Att10] [Ent10] | Q_21 [Att22] [Ent10] | Sub_21 [Att10] [Ent10] | Sup_21 [Att10] [Ent10] | Tt_21 [Att10] [Ent10] | I_21 [Att10] [Ent10] | B_21 [Att10] [Ent10] | Big_21 [Att10] [Ent10] | Small_21 [Att10] [Ent10] | U_21 [Att10] [Ent10] | S_21 [Att10] [Ent10] | Strike_21 [Att10] [Ent10] | Basefont_21 [Att28] | Font_21 [Att30] [Ent10] | Object_21 [Att31] [Ent21] | Param_21 [Att32] | Applet_21 [Att34] [Ent21] | Img_21 [Att37] | Map_21 [Att40] [Ent22] | Form_21 [Att43] [Ent14] | Label_21 [Att45] [Ent23] | Input_21 [Att46] | Select_21 [Att47] [Ent31] | Textarea_21 [Att51] [Ent2] | Fieldset_21 [Att10] [Ent20] | Button_21 [Att55] [Ent33] | Isindex_21 [Att56] | Table_21 [Att57] [Ent16] | PCDATA_21 [Att0] B.ByteString deriving (Show) data Ent22 = Script_22 [Att9] [Ent2] | Noscript_22 [Att10] [Ent11] | Div_22 [Att15] [Ent11] | P_22 [Att15] [Ent10] | H1_22 [Att15] [Ent10] | H2_22 [Att15] [Ent10] | H3_22 [Att15] [Ent10] | H4_22 [Att15] [Ent10] | H5_22 [Att15] [Ent10] | H6_22 [Att15] [Ent10] | Ul_22 [Att16] [Ent6] | Ol_22 [Att17] [Ent6] | Menu_22 [Att18] [Ent6] | Dir_22 [Att18] [Ent6] | Dl_22 [Att18] [Ent7] | Address_22 [Att10] [Ent12] | Hr_22 [Att20] | Pre_22 [Att21] [Ent13] | Blockquote_22 [Att22] [Ent11] | Center_22 [Att10] [Ent11] | Ins_22 [Att23] [Ent11] | Del_22 [Att23] [Ent11] | Area_22 [Att42] | Form_22 [Att43] [Ent14] | Fieldset_22 [Att10] [Ent20] | Isindex_22 [Att56] | Table_22 [Att57] [Ent16] deriving (Show) data Ent23 = Script_23 [Att9] [Ent2] | Iframe_23 [Att13] [Ent24] | Ins_23 [Att23] [Ent24] | Del_23 [Att23] [Ent24] | Span_23 [Att10] [Ent23] | Bdo_23 [Att10] [Ent23] | Br_23 [Att27] | Em_23 [Att10] [Ent23] | Strong_23 [Att10] [Ent23] | Dfn_23 [Att10] [Ent23] | Code_23 [Att10] [Ent23] | Samp_23 [Att10] [Ent23] | Kbd_23 [Att10] [Ent23] | Var_23 [Att10] [Ent23] | Cite_23 [Att10] [Ent23] | Abbr_23 [Att10] [Ent23] | Acronym_23 [Att10] [Ent23] | Q_23 [Att22] [Ent23] | Sub_23 [Att10] [Ent23] | Sup_23 [Att10] [Ent23] | Tt_23 [Att10] [Ent23] | I_23 [Att10] [Ent23] | B_23 [Att10] [Ent23] | Big_23 [Att10] [Ent23] | Small_23 [Att10] [Ent23] | U_23 [Att10] [Ent23] | S_23 [Att10] [Ent23] | Strike_23 [Att10] [Ent23] | Basefont_23 [Att28] | Font_23 [Att30] [Ent23] | Object_23 [Att31] [Ent30] | Applet_23 [Att34] [Ent30] | Img_23 [Att37] | Map_23 [Att40] [Ent22] | Input_23 [Att46] | Select_23 [Att47] [Ent31] | Textarea_23 [Att51] [Ent2] | Button_23 [Att55] [Ent33] | PCDATA_23 [Att0] B.ByteString deriving (Show) data Ent24 = Script_24 [Att9] [Ent2] | Noscript_24 [Att10] [Ent24] | Iframe_24 [Att13] [Ent24] | Div_24 [Att15] [Ent24] | P_24 [Att15] [Ent23] | H1_24 [Att15] [Ent23] | H2_24 [Att15] [Ent23] | H3_24 [Att15] [Ent23] | H4_24 [Att15] [Ent23] | H5_24 [Att15] [Ent23] | H6_24 [Att15] [Ent23] | Ul_24 [Att16] [Ent6] | Ol_24 [Att17] [Ent6] | Menu_24 [Att18] [Ent6] | Dir_24 [Att18] [Ent6] | Dl_24 [Att18] [Ent7] | Address_24 [Att10] [Ent25] | Hr_24 [Att20] | Pre_24 [Att21] [Ent26] | Blockquote_24 [Att22] [Ent24] | Center_24 [Att10] [Ent24] | Ins_24 [Att23] [Ent24] | Del_24 [Att23] [Ent24] | Span_24 [Att10] [Ent23] | Bdo_24 [Att10] [Ent23] | Br_24 [Att27] | Em_24 [Att10] [Ent23] | Strong_24 [Att10] [Ent23] | Dfn_24 [Att10] [Ent23] | Code_24 [Att10] [Ent23] | Samp_24 [Att10] [Ent23] | Kbd_24 [Att10] [Ent23] | Var_24 [Att10] [Ent23] | Cite_24 [Att10] [Ent23] | Abbr_24 [Att10] [Ent23] | Acronym_24 [Att10] [Ent23] | Q_24 [Att22] [Ent23] | Sub_24 [Att10] [Ent23] | Sup_24 [Att10] [Ent23] | Tt_24 [Att10] [Ent23] | I_24 [Att10] [Ent23] | B_24 [Att10] [Ent23] | Big_24 [Att10] [Ent23] | Small_24 [Att10] [Ent23] | U_24 [Att10] [Ent23] | S_24 [Att10] [Ent23] | Strike_24 [Att10] [Ent23] | Basefont_24 [Att28] | Font_24 [Att30] [Ent23] | Object_24 [Att31] [Ent30] | Applet_24 [Att34] [Ent30] | Img_24 [Att37] | Map_24 [Att40] [Ent22] | Form_24 [Att43] [Ent27] | Input_24 [Att46] | Select_24 [Att47] [Ent31] | Textarea_24 [Att51] [Ent2] | Fieldset_24 [Att10] [Ent29] | Button_24 [Att55] [Ent33] | Isindex_24 [Att56] | Table_24 [Att57] [Ent16] | PCDATA_24 [Att0] B.ByteString deriving (Show) data Ent25 = Script_25 [Att9] [Ent2] | Iframe_25 [Att13] [Ent24] | P_25 [Att15] [Ent23] | Ins_25 [Att23] [Ent24] | Del_25 [Att23] [Ent24] | Span_25 [Att10] [Ent23] | Bdo_25 [Att10] [Ent23] | Br_25 [Att27] | Em_25 [Att10] [Ent23] | Strong_25 [Att10] [Ent23] | Dfn_25 [Att10] [Ent23] | Code_25 [Att10] [Ent23] | Samp_25 [Att10] [Ent23] | Kbd_25 [Att10] [Ent23] | Var_25 [Att10] [Ent23] | Cite_25 [Att10] [Ent23] | Abbr_25 [Att10] [Ent23] | Acronym_25 [Att10] [Ent23] | Q_25 [Att22] [Ent23] | Sub_25 [Att10] [Ent23] | Sup_25 [Att10] [Ent23] | Tt_25 [Att10] [Ent23] | I_25 [Att10] [Ent23] | B_25 [Att10] [Ent23] | Big_25 [Att10] [Ent23] | Small_25 [Att10] [Ent23] | U_25 [Att10] [Ent23] | S_25 [Att10] [Ent23] | Strike_25 [Att10] [Ent23] | Basefont_25 [Att28] | Font_25 [Att30] [Ent23] | Object_25 [Att31] [Ent30] | Applet_25 [Att34] [Ent30] | Img_25 [Att37] | Map_25 [Att40] [Ent22] | Input_25 [Att46] | Select_25 [Att47] [Ent31] | Textarea_25 [Att51] [Ent2] | Button_25 [Att55] [Ent33] | PCDATA_25 [Att0] B.ByteString deriving (Show) data Ent26 = Script_26 [Att9] [Ent2] | Ins_26 [Att23] [Ent24] | Del_26 [Att23] [Ent24] | Span_26 [Att10] [Ent23] | Bdo_26 [Att10] [Ent23] | Br_26 [Att27] | Em_26 [Att10] [Ent23] | Strong_26 [Att10] [Ent23] | Dfn_26 [Att10] [Ent23] | Code_26 [Att10] [Ent23] | Samp_26 [Att10] [Ent23] | Kbd_26 [Att10] [Ent23] | Var_26 [Att10] [Ent23] | Cite_26 [Att10] [Ent23] | Abbr_26 [Att10] [Ent23] | Acronym_26 [Att10] [Ent23] | Q_26 [Att22] [Ent23] | Tt_26 [Att10] [Ent23] | I_26 [Att10] [Ent23] | B_26 [Att10] [Ent23] | U_26 [Att10] [Ent23] | S_26 [Att10] [Ent23] | Strike_26 [Att10] [Ent23] | Input_26 [Att46] | Select_26 [Att47] [Ent31] | Textarea_26 [Att51] [Ent2] | Button_26 [Att55] [Ent33] | PCDATA_26 [Att0] B.ByteString deriving (Show) data Ent27 = Script_27 [Att9] [Ent2] | Noscript_27 [Att10] [Ent27] | Iframe_27 [Att13] [Ent27] | Div_27 [Att15] [Ent27] | P_27 [Att15] [Ent23] | H1_27 [Att15] [Ent23] | H2_27 [Att15] [Ent23] | H3_27 [Att15] [Ent23] | H4_27 [Att15] [Ent23] | H5_27 [Att15] [Ent23] | H6_27 [Att15] [Ent23] | Ul_27 [Att16] [Ent6] | Ol_27 [Att17] [Ent6] | Menu_27 [Att18] [Ent6] | Dir_27 [Att18] [Ent6] | Dl_27 [Att18] [Ent7] | Address_27 [Att10] [Ent25] | Hr_27 [Att20] | Pre_27 [Att21] [Ent26] | Blockquote_27 [Att22] [Ent27] | Center_27 [Att10] [Ent27] | Ins_27 [Att23] [Ent27] | Del_27 [Att23] [Ent27] | Span_27 [Att10] [Ent23] | Bdo_27 [Att10] [Ent23] | Br_27 [Att27] | Em_27 [Att10] [Ent23] | Strong_27 [Att10] [Ent23] | Dfn_27 [Att10] [Ent23] | Code_27 [Att10] [Ent23] | Samp_27 [Att10] [Ent23] | Kbd_27 [Att10] [Ent23] | Var_27 [Att10] [Ent23] | Cite_27 [Att10] [Ent23] | Abbr_27 [Att10] [Ent23] | Acronym_27 [Att10] [Ent23] | Q_27 [Att22] [Ent23] | Sub_27 [Att10] [Ent23] | Sup_27 [Att10] [Ent23] | Tt_27 [Att10] [Ent23] | I_27 [Att10] [Ent23] | B_27 [Att10] [Ent23] | Big_27 [Att10] [Ent23] | Small_27 [Att10] [Ent23] | U_27 [Att10] [Ent23] | S_27 [Att10] [Ent23] | Strike_27 [Att10] [Ent23] | Basefont_27 [Att28] | Font_27 [Att30] [Ent23] | Object_27 [Att31] [Ent37] | Applet_27 [Att34] [Ent37] | Img_27 [Att37] | Map_27 [Att40] [Ent36] | Input_27 [Att46] | Select_27 [Att47] [Ent31] | Textarea_27 [Att51] [Ent2] | Fieldset_27 [Att10] [Ent28] | Button_27 [Att55] [Ent33] | Isindex_27 [Att56] | Table_27 [Att57] [Ent16] | PCDATA_27 [Att0] B.ByteString deriving (Show) data Ent28 = Script_28 [Att9] [Ent2] | Noscript_28 [Att10] [Ent27] | Iframe_28 [Att13] [Ent27] | Div_28 [Att15] [Ent27] | P_28 [Att15] [Ent23] | H1_28 [Att15] [Ent23] | H2_28 [Att15] [Ent23] | H3_28 [Att15] [Ent23] | H4_28 [Att15] [Ent23] | H5_28 [Att15] [Ent23] | H6_28 [Att15] [Ent23] | Ul_28 [Att16] [Ent6] | Ol_28 [Att17] [Ent6] | Menu_28 [Att18] [Ent6] | Dir_28 [Att18] [Ent6] | Dl_28 [Att18] [Ent7] | Address_28 [Att10] [Ent25] | Hr_28 [Att20] | Pre_28 [Att21] [Ent26] | Blockquote_28 [Att22] [Ent27] | Center_28 [Att10] [Ent27] | Ins_28 [Att23] [Ent27] | Del_28 [Att23] [Ent27] | Span_28 [Att10] [Ent23] | Bdo_28 [Att10] [Ent23] | Br_28 [Att27] | Em_28 [Att10] [Ent23] | Strong_28 [Att10] [Ent23] | Dfn_28 [Att10] [Ent23] | Code_28 [Att10] [Ent23] | Samp_28 [Att10] [Ent23] | Kbd_28 [Att10] [Ent23] | Var_28 [Att10] [Ent23] | Cite_28 [Att10] [Ent23] | Abbr_28 [Att10] [Ent23] | Acronym_28 [Att10] [Ent23] | Q_28 [Att22] [Ent23] | Sub_28 [Att10] [Ent23] | Sup_28 [Att10] [Ent23] | Tt_28 [Att10] [Ent23] | I_28 [Att10] [Ent23] | B_28 [Att10] [Ent23] | Big_28 [Att10] [Ent23] | Small_28 [Att10] [Ent23] | U_28 [Att10] [Ent23] | S_28 [Att10] [Ent23] | Strike_28 [Att10] [Ent23] | Basefont_28 [Att28] | Font_28 [Att30] [Ent23] | Object_28 [Att31] [Ent37] | Applet_28 [Att34] [Ent37] | Img_28 [Att37] | Map_28 [Att40] [Ent36] | Input_28 [Att46] | Select_28 [Att47] [Ent31] | Textarea_28 [Att51] [Ent2] | Fieldset_28 [Att10] [Ent28] | Legend_28 [Att54] [Ent23] | Button_28 [Att55] [Ent33] | Isindex_28 [Att56] | Table_28 [Att57] [Ent16] | PCDATA_28 [Att0] B.ByteString deriving (Show) data Ent29 = Script_29 [Att9] [Ent2] | Noscript_29 [Att10] [Ent24] | Iframe_29 [Att13] [Ent24] | Div_29 [Att15] [Ent24] | P_29 [Att15] [Ent23] | H1_29 [Att15] [Ent23] | H2_29 [Att15] [Ent23] | H3_29 [Att15] [Ent23] | H4_29 [Att15] [Ent23] | H5_29 [Att15] [Ent23] | H6_29 [Att15] [Ent23] | Ul_29 [Att16] [Ent6] | Ol_29 [Att17] [Ent6] | Menu_29 [Att18] [Ent6] | Dir_29 [Att18] [Ent6] | Dl_29 [Att18] [Ent7] | Address_29 [Att10] [Ent25] | Hr_29 [Att20] | Pre_29 [Att21] [Ent26] | Blockquote_29 [Att22] [Ent24] | Center_29 [Att10] [Ent24] | Ins_29 [Att23] [Ent24] | Del_29 [Att23] [Ent24] | Span_29 [Att10] [Ent23] | Bdo_29 [Att10] [Ent23] | Br_29 [Att27] | Em_29 [Att10] [Ent23] | Strong_29 [Att10] [Ent23] | Dfn_29 [Att10] [Ent23] | Code_29 [Att10] [Ent23] | Samp_29 [Att10] [Ent23] | Kbd_29 [Att10] [Ent23] | Var_29 [Att10] [Ent23] | Cite_29 [Att10] [Ent23] | Abbr_29 [Att10] [Ent23] | Acronym_29 [Att10] [Ent23] | Q_29 [Att22] [Ent23] | Sub_29 [Att10] [Ent23] | Sup_29 [Att10] [Ent23] | Tt_29 [Att10] [Ent23] | I_29 [Att10] [Ent23] | B_29 [Att10] [Ent23] | Big_29 [Att10] [Ent23] | Small_29 [Att10] [Ent23] | U_29 [Att10] [Ent23] | S_29 [Att10] [Ent23] | Strike_29 [Att10] [Ent23] | Basefont_29 [Att28] | Font_29 [Att30] [Ent23] | Object_29 [Att31] [Ent30] | Applet_29 [Att34] [Ent30] | Img_29 [Att37] | Map_29 [Att40] [Ent22] | Form_29 [Att43] [Ent27] | Input_29 [Att46] | Select_29 [Att47] [Ent31] | Textarea_29 [Att51] [Ent2] | Fieldset_29 [Att10] [Ent29] | Legend_29 [Att54] [Ent23] | Button_29 [Att55] [Ent33] | Isindex_29 [Att56] | Table_29 [Att57] [Ent16] | PCDATA_29 [Att0] B.ByteString deriving (Show) data Ent30 = Script_30 [Att9] [Ent2] | Noscript_30 [Att10] [Ent24] | Iframe_30 [Att13] [Ent24] | Div_30 [Att15] [Ent24] | P_30 [Att15] [Ent23] | H1_30 [Att15] [Ent23] | H2_30 [Att15] [Ent23] | H3_30 [Att15] [Ent23] | H4_30 [Att15] [Ent23] | H5_30 [Att15] [Ent23] | H6_30 [Att15] [Ent23] | Ul_30 [Att16] [Ent6] | Ol_30 [Att17] [Ent6] | Menu_30 [Att18] [Ent6] | Dir_30 [Att18] [Ent6] | Dl_30 [Att18] [Ent7] | Address_30 [Att10] [Ent25] | Hr_30 [Att20] | Pre_30 [Att21] [Ent26] | Blockquote_30 [Att22] [Ent24] | Center_30 [Att10] [Ent24] | Ins_30 [Att23] [Ent24] | Del_30 [Att23] [Ent24] | Span_30 [Att10] [Ent23] | Bdo_30 [Att10] [Ent23] | Br_30 [Att27] | Em_30 [Att10] [Ent23] | Strong_30 [Att10] [Ent23] | Dfn_30 [Att10] [Ent23] | Code_30 [Att10] [Ent23] | Samp_30 [Att10] [Ent23] | Kbd_30 [Att10] [Ent23] | Var_30 [Att10] [Ent23] | Cite_30 [Att10] [Ent23] | Abbr_30 [Att10] [Ent23] | Acronym_30 [Att10] [Ent23] | Q_30 [Att22] [Ent23] | Sub_30 [Att10] [Ent23] | Sup_30 [Att10] [Ent23] | Tt_30 [Att10] [Ent23] | I_30 [Att10] [Ent23] | B_30 [Att10] [Ent23] | Big_30 [Att10] [Ent23] | Small_30 [Att10] [Ent23] | U_30 [Att10] [Ent23] | S_30 [Att10] [Ent23] | Strike_30 [Att10] [Ent23] | Basefont_30 [Att28] | Font_30 [Att30] [Ent23] | Object_30 [Att31] [Ent30] | Param_30 [Att32] | Applet_30 [Att34] [Ent30] | Img_30 [Att37] | Map_30 [Att40] [Ent22] | Form_30 [Att43] [Ent27] | Input_30 [Att46] | Select_30 [Att47] [Ent31] | Textarea_30 [Att51] [Ent2] | Fieldset_30 [Att10] [Ent29] | Button_30 [Att55] [Ent33] | Isindex_30 [Att56] | Table_30 [Att57] [Ent16] | PCDATA_30 [Att0] B.ByteString deriving (Show) data Ent31 = Optgroup_31 [Att48] [Ent32] | Option_31 [Att50] [Ent2] deriving (Show) data Ent32 = Option_32 [Att50] [Ent2] deriving (Show) data Ent33 = Script_33 [Att9] [Ent2] | Noscript_33 [Att10] [Ent24] | Div_33 [Att15] [Ent24] | P_33 [Att15] [Ent23] | H1_33 [Att15] [Ent23] | H2_33 [Att15] [Ent23] | H3_33 [Att15] [Ent23] | H4_33 [Att15] [Ent23] | H5_33 [Att15] [Ent23] | H6_33 [Att15] [Ent23] | Ul_33 [Att16] [Ent6] | Ol_33 [Att17] [Ent6] | Menu_33 [Att18] [Ent6] | Dir_33 [Att18] [Ent6] | Dl_33 [Att18] [Ent7] | Address_33 [Att10] [Ent25] | Hr_33 [Att20] | Pre_33 [Att21] [Ent26] | Blockquote_33 [Att22] [Ent24] | Center_33 [Att10] [Ent24] | Ins_33 [Att23] [Ent24] | Del_33 [Att23] [Ent24] | Span_33 [Att10] [Ent23] | Bdo_33 [Att10] [Ent23] | Br_33 [Att27] | Em_33 [Att10] [Ent23] | Strong_33 [Att10] [Ent23] | Dfn_33 [Att10] [Ent23] | Code_33 [Att10] [Ent23] | Samp_33 [Att10] [Ent23] | Kbd_33 [Att10] [Ent23] | Var_33 [Att10] [Ent23] | Cite_33 [Att10] [Ent23] | Abbr_33 [Att10] [Ent23] | Acronym_33 [Att10] [Ent23] | Q_33 [Att22] [Ent23] | Sub_33 [Att10] [Ent23] | Sup_33 [Att10] [Ent23] | Tt_33 [Att10] [Ent23] | I_33 [Att10] [Ent23] | B_33 [Att10] [Ent23] | Big_33 [Att10] [Ent23] | Small_33 [Att10] [Ent23] | U_33 [Att10] [Ent23] | S_33 [Att10] [Ent23] | Strike_33 [Att10] [Ent23] | Basefont_33 [Att28] | Font_33 [Att30] [Ent23] | Object_33 [Att31] [Ent30] | Applet_33 [Att34] [Ent30] | Img_33 [Att37] | Map_33 [Att40] [Ent22] | Table_33 [Att57] [Ent16] | PCDATA_33 [Att0] B.ByteString deriving (Show) data Ent34 = Script_34 [Att9] [Ent2] | Noscript_34 [Att10] [Ent34] | Iframe_34 [Att13] [Ent34] | Div_34 [Att15] [Ent34] | P_34 [Att15] [Ent5] | H1_34 [Att15] [Ent5] | H2_34 [Att15] [Ent5] | H3_34 [Att15] [Ent5] | H4_34 [Att15] [Ent5] | H5_34 [Att15] [Ent5] | H6_34 [Att15] [Ent5] | Ul_34 [Att16] [Ent6] | Ol_34 [Att17] [Ent6] | Menu_34 [Att18] [Ent6] | Dir_34 [Att18] [Ent6] | Dl_34 [Att18] [Ent7] | Address_34 [Att10] [Ent8] | Hr_34 [Att20] | Pre_34 [Att21] [Ent9] | Blockquote_34 [Att22] [Ent34] | Center_34 [Att10] [Ent34] | Ins_34 [Att23] [Ent34] | Del_34 [Att23] [Ent34] | A_34 [Att24] [Ent10] | Span_34 [Att10] [Ent5] | Bdo_34 [Att10] [Ent5] | Br_34 [Att27] | Em_34 [Att10] [Ent5] | Strong_34 [Att10] [Ent5] | Dfn_34 [Att10] [Ent5] | Code_34 [Att10] [Ent5] | Samp_34 [Att10] [Ent5] | Kbd_34 [Att10] [Ent5] | Var_34 [Att10] [Ent5] | Cite_34 [Att10] [Ent5] | Abbr_34 [Att10] [Ent5] | Acronym_34 [Att10] [Ent5] | Q_34 [Att22] [Ent5] | Sub_34 [Att10] [Ent5] | Sup_34 [Att10] [Ent5] | Tt_34 [Att10] [Ent5] | I_34 [Att10] [Ent5] | B_34 [Att10] [Ent5] | Big_34 [Att10] [Ent5] | Small_34 [Att10] [Ent5] | U_34 [Att10] [Ent5] | S_34 [Att10] [Ent5] | Strike_34 [Att10] [Ent5] | Basefont_34 [Att28] | Font_34 [Att30] [Ent5] | Object_34 [Att31] [Ent38] | Applet_34 [Att34] [Ent38] | Img_34 [Att37] | Map_34 [Att40] [Ent36] | Label_34 [Att45] [Ent39] | Input_34 [Att46] | Select_34 [Att47] [Ent31] | Textarea_34 [Att51] [Ent2] | Fieldset_34 [Att10] [Ent45] | Button_34 [Att55] [Ent33] | Isindex_34 [Att56] | Table_34 [Att57] [Ent16] | PCDATA_34 [Att0] B.ByteString deriving (Show) data Ent35 = Script_35 [Att9] [Ent2] | Noscript_35 [Att10] [Ent14] | Iframe_35 [Att13] [Ent14] | Div_35 [Att15] [Ent14] | P_35 [Att15] [Ent10] | H1_35 [Att15] [Ent10] | H2_35 [Att15] [Ent10] | H3_35 [Att15] [Ent10] | H4_35 [Att15] [Ent10] | H5_35 [Att15] [Ent10] | H6_35 [Att15] [Ent10] | Ul_35 [Att16] [Ent6] | Ol_35 [Att17] [Ent6] | Menu_35 [Att18] [Ent2] | Dir_35 [Att18] [Ent6] | Dl_35 [Att18] [Ent7] | Address_35 [Att10] [Ent12] | Hr_35 [Att20] | Pre_35 [Att21] [Ent13] | Blockquote_35 [Att22] [Ent14] | Center_35 [Att10] [Ent14] | Ins_35 [Att23] [Ent14] | Del_35 [Att23] [Ent14] | Span_35 [Att10] [Ent10] | Bdo_35 [Att10] [Ent10] | Br_35 [Att27] | Em_35 [Att10] [Ent10] | Strong_35 [Att10] [Ent10] | Dfn_35 [Att10] [Ent10] | Code_35 [Att10] [Ent10] | Samp_35 [Att10] [Ent10] | Kbd_35 [Att10] [Ent10] | Var_35 [Att10] [Ent10] | Cite_35 [Att10] [Ent10] | Abbr_35 [Att10] [Ent10] | Acronym_35 [Att10] [Ent10] | Q_35 [Att22] [Ent10] | Sub_35 [Att10] [Ent10] | Sup_35 [Att10] [Ent10] | Tt_35 [Att10] [Ent10] | I_35 [Att10] [Ent10] | B_35 [Att10] [Ent10] | Big_35 [Att10] [Ent10] | Small_35 [Att10] [Ent10] | U_35 [Att10] [Ent10] | S_35 [Att10] [Ent10] | Strike_35 [Att10] [Ent10] | Basefont_35 [Att28] | Font_35 [Att30] [Ent10] | Object_35 [Att31] [Ent35] | Param_35 [Att32] | Applet_35 [Att34] [Ent35] | Img_35 [Att37] | Map_35 [Att40] [Ent36] | Label_35 [Att45] [Ent23] | Input_35 [Att46] | Select_35 [Att47] [Ent31] | Textarea_35 [Att51] [Ent2] | Fieldset_35 [Att10] [Ent15] | Button_35 [Att55] [Ent33] | Isindex_35 [Att56] | Table_35 [Att57] [Ent16] | PCDATA_35 [Att0] B.ByteString deriving (Show) data Ent36 = Script_36 [Att9] [Ent2] | Noscript_36 [Att10] [Ent14] | Div_36 [Att15] [Ent14] | P_36 [Att15] [Ent10] | H1_36 [Att15] [Ent10] | H2_36 [Att15] [Ent10] | H3_36 [Att15] [Ent10] | H4_36 [Att15] [Ent10] | H5_36 [Att15] [Ent10] | H6_36 [Att15] [Ent10] | Ul_36 [Att16] [Ent6] | Ol_36 [Att17] [Ent6] | Menu_36 [Att18] [Ent2] | Dir_36 [Att18] [Ent6] | Dl_36 [Att18] [Ent7] | Address_36 [Att10] [Ent12] | Hr_36 [Att20] | Pre_36 [Att21] [Ent13] | Blockquote_36 [Att22] [Ent14] | Center_36 [Att10] [Ent14] | Ins_36 [Att23] [Ent14] | Del_36 [Att23] [Ent14] | Area_36 [Att42] | Fieldset_36 [Att10] [Ent15] | Isindex_36 [Att56] | Table_36 [Att57] [Ent16] deriving (Show) data Ent37 = Script_37 [Att9] [Ent2] | Noscript_37 [Att10] [Ent27] | Iframe_37 [Att13] [Ent27] | Div_37 [Att15] [Ent27] | P_37 [Att15] [Ent23] | H1_37 [Att15] [Ent23] | H2_37 [Att15] [Ent23] | H3_37 [Att15] [Ent23] | H4_37 [Att15] [Ent23] | H5_37 [Att15] [Ent23] | H6_37 [Att15] [Ent23] | Ul_37 [Att16] [Ent6] | Ol_37 [Att17] [Ent6] | Menu_37 [Att18] [Ent6] | Dir_37 [Att18] [Ent6] | Dl_37 [Att18] [Ent7] | Address_37 [Att10] [Ent25] | Hr_37 [Att20] | Pre_37 [Att21] [Ent26] | Blockquote_37 [Att22] [Ent27] | Center_37 [Att10] [Ent27] | Ins_37 [Att23] [Ent27] | Del_37 [Att23] [Ent27] | Span_37 [Att10] [Ent23] | Bdo_37 [Att10] [Ent23] | Br_37 [Att27] | Em_37 [Att10] [Ent23] | Strong_37 [Att10] [Ent23] | Dfn_37 [Att10] [Ent23] | Code_37 [Att10] [Ent23] | Samp_37 [Att10] [Ent23] | Kbd_37 [Att10] [Ent23] | Var_37 [Att10] [Ent23] | Cite_37 [Att10] [Ent23] | Abbr_37 [Att10] [Ent23] | Acronym_37 [Att10] [Ent23] | Q_37 [Att22] [Ent23] | Sub_37 [Att10] [Ent23] | Sup_37 [Att10] [Ent23] | Tt_37 [Att10] [Ent23] | I_37 [Att10] [Ent23] | B_37 [Att10] [Ent23] | Big_37 [Att10] [Ent23] | Small_37 [Att10] [Ent23] | U_37 [Att10] [Ent23] | S_37 [Att10] [Ent23] | Strike_37 [Att10] [Ent23] | Basefont_37 [Att28] | Font_37 [Att30] [Ent23] | Object_37 [Att31] [Ent37] | Param_37 [Att32] | Applet_37 [Att34] [Ent37] | Img_37 [Att37] | Map_37 [Att40] [Ent36] | Input_37 [Att46] | Select_37 [Att47] [Ent31] | Textarea_37 [Att51] [Ent2] | Fieldset_37 [Att10] [Ent28] | Button_37 [Att55] [Ent33] | Isindex_37 [Att56] | Table_37 [Att57] [Ent16] | PCDATA_37 [Att0] B.ByteString deriving (Show) data Ent38 = Script_38 [Att9] [Ent2] | Noscript_38 [Att10] [Ent34] | Iframe_38 [Att13] [Ent34] | Div_38 [Att15] [Ent34] | P_38 [Att15] [Ent5] | H1_38 [Att15] [Ent5] | H2_38 [Att15] [Ent5] | H3_38 [Att15] [Ent5] | H4_38 [Att15] [Ent5] | H5_38 [Att15] [Ent5] | H6_38 [Att15] [Ent5] | Ul_38 [Att16] [Ent6] | Ol_38 [Att17] [Ent6] | Menu_38 [Att18] [Ent6] | Dir_38 [Att18] [Ent6] | Dl_38 [Att18] [Ent7] | Address_38 [Att10] [Ent8] | Hr_38 [Att20] | Pre_38 [Att21] [Ent9] | Blockquote_38 [Att22] [Ent34] | Center_38 [Att10] [Ent34] | Ins_38 [Att23] [Ent34] | Del_38 [Att23] [Ent34] | A_38 [Att24] [Ent10] | Span_38 [Att10] [Ent5] | Bdo_38 [Att10] [Ent5] | Br_38 [Att27] | Em_38 [Att10] [Ent5] | Strong_38 [Att10] [Ent5] | Dfn_38 [Att10] [Ent5] | Code_38 [Att10] [Ent5] | Samp_38 [Att10] [Ent5] | Kbd_38 [Att10] [Ent5] | Var_38 [Att10] [Ent5] | Cite_38 [Att10] [Ent5] | Abbr_38 [Att10] [Ent5] | Acronym_38 [Att10] [Ent5] | Q_38 [Att22] [Ent5] | Sub_38 [Att10] [Ent5] | Sup_38 [Att10] [Ent5] | Tt_38 [Att10] [Ent5] | I_38 [Att10] [Ent5] | B_38 [Att10] [Ent5] | Big_38 [Att10] [Ent5] | Small_38 [Att10] [Ent5] | U_38 [Att10] [Ent5] | S_38 [Att10] [Ent5] | Strike_38 [Att10] [Ent5] | Basefont_38 [Att28] | Font_38 [Att30] [Ent5] | Object_38 [Att31] [Ent38] | Param_38 [Att32] | Applet_38 [Att34] [Ent38] | Img_38 [Att37] | Map_38 [Att40] [Ent36] | Label_38 [Att45] [Ent39] | Input_38 [Att46] | Select_38 [Att47] [Ent31] | Textarea_38 [Att51] [Ent2] | Fieldset_38 [Att10] [Ent45] | Button_38 [Att55] [Ent33] | Isindex_38 [Att56] | Table_38 [Att57] [Ent16] | PCDATA_38 [Att0] B.ByteString deriving (Show) data Ent39 = Script_39 [Att9] [Ent2] | Iframe_39 [Att13] [Ent40] | Ins_39 [Att23] [Ent40] | Del_39 [Att23] [Ent40] | A_39 [Att24] [Ent23] | Span_39 [Att10] [Ent39] | Bdo_39 [Att10] [Ent39] | Br_39 [Att27] | Em_39 [Att10] [Ent39] | Strong_39 [Att10] [Ent39] | Dfn_39 [Att10] [Ent39] | Code_39 [Att10] [Ent39] | Samp_39 [Att10] [Ent39] | Kbd_39 [Att10] [Ent39] | Var_39 [Att10] [Ent39] | Cite_39 [Att10] [Ent39] | Abbr_39 [Att10] [Ent39] | Acronym_39 [Att10] [Ent39] | Q_39 [Att22] [Ent39] | Sub_39 [Att10] [Ent39] | Sup_39 [Att10] [Ent39] | Tt_39 [Att10] [Ent39] | I_39 [Att10] [Ent39] | B_39 [Att10] [Ent39] | Big_39 [Att10] [Ent39] | Small_39 [Att10] [Ent39] | U_39 [Att10] [Ent39] | S_39 [Att10] [Ent39] | Strike_39 [Att10] [Ent39] | Basefont_39 [Att28] | Font_39 [Att30] [Ent39] | Object_39 [Att31] [Ent44] | Applet_39 [Att34] [Ent44] | Img_39 [Att37] | Map_39 [Att40] [Ent36] | Input_39 [Att46] | Select_39 [Att47] [Ent31] | Textarea_39 [Att51] [Ent2] | Button_39 [Att55] [Ent33] | PCDATA_39 [Att0] B.ByteString deriving (Show) data Ent40 = Script_40 [Att9] [Ent2] | Noscript_40 [Att10] [Ent40] | Iframe_40 [Att13] [Ent40] | Div_40 [Att15] [Ent40] | P_40 [Att15] [Ent39] | H1_40 [Att15] [Ent39] | H2_40 [Att15] [Ent39] | H3_40 [Att15] [Ent39] | H4_40 [Att15] [Ent39] | H5_40 [Att15] [Ent39] | H6_40 [Att15] [Ent39] | Ul_40 [Att16] [Ent6] | Ol_40 [Att17] [Ent6] | Menu_40 [Att18] [Ent6] | Dir_40 [Att18] [Ent6] | Dl_40 [Att18] [Ent7] | Address_40 [Att10] [Ent41] | Hr_40 [Att20] | Pre_40 [Att21] [Ent42] | Blockquote_40 [Att22] [Ent40] | Center_40 [Att10] [Ent40] | Ins_40 [Att23] [Ent40] | Del_40 [Att23] [Ent40] | A_40 [Att24] [Ent23] | Span_40 [Att10] [Ent39] | Bdo_40 [Att10] [Ent39] | Br_40 [Att27] | Em_40 [Att10] [Ent39] | Strong_40 [Att10] [Ent39] | Dfn_40 [Att10] [Ent39] | Code_40 [Att10] [Ent39] | Samp_40 [Att10] [Ent39] | Kbd_40 [Att10] [Ent39] | Var_40 [Att10] [Ent39] | Cite_40 [Att10] [Ent39] | Abbr_40 [Att10] [Ent39] | Acronym_40 [Att10] [Ent39] | Q_40 [Att22] [Ent39] | Sub_40 [Att10] [Ent39] | Sup_40 [Att10] [Ent39] | Tt_40 [Att10] [Ent39] | I_40 [Att10] [Ent39] | B_40 [Att10] [Ent39] | Big_40 [Att10] [Ent39] | Small_40 [Att10] [Ent39] | U_40 [Att10] [Ent39] | S_40 [Att10] [Ent39] | Strike_40 [Att10] [Ent39] | Basefont_40 [Att28] | Font_40 [Att30] [Ent39] | Object_40 [Att31] [Ent44] | Applet_40 [Att34] [Ent44] | Img_40 [Att37] | Map_40 [Att40] [Ent36] | Input_40 [Att46] | Select_40 [Att47] [Ent31] | Textarea_40 [Att51] [Ent2] | Fieldset_40 [Att10] [Ent43] | Button_40 [Att55] [Ent33] | Isindex_40 [Att56] | Table_40 [Att57] [Ent16] | PCDATA_40 [Att0] B.ByteString deriving (Show) data Ent41 = Script_41 [Att9] [Ent2] | Iframe_41 [Att13] [Ent40] | P_41 [Att15] [Ent39] | Ins_41 [Att23] [Ent40] | Del_41 [Att23] [Ent40] | A_41 [Att24] [Ent23] | Span_41 [Att10] [Ent39] | Bdo_41 [Att10] [Ent39] | Br_41 [Att27] | Em_41 [Att10] [Ent39] | Strong_41 [Att10] [Ent39] | Dfn_41 [Att10] [Ent39] | Code_41 [Att10] [Ent39] | Samp_41 [Att10] [Ent39] | Kbd_41 [Att10] [Ent39] | Var_41 [Att10] [Ent39] | Cite_41 [Att10] [Ent39] | Abbr_41 [Att10] [Ent39] | Acronym_41 [Att10] [Ent39] | Q_41 [Att22] [Ent39] | Sub_41 [Att10] [Ent39] | Sup_41 [Att10] [Ent39] | Tt_41 [Att10] [Ent39] | I_41 [Att10] [Ent39] | B_41 [Att10] [Ent39] | Big_41 [Att10] [Ent39] | Small_41 [Att10] [Ent39] | U_41 [Att10] [Ent39] | S_41 [Att10] [Ent39] | Strike_41 [Att10] [Ent39] | Basefont_41 [Att28] | Font_41 [Att30] [Ent39] | Object_41 [Att31] [Ent44] | Applet_41 [Att34] [Ent44] | Img_41 [Att37] | Map_41 [Att40] [Ent36] | Input_41 [Att46] | Select_41 [Att47] [Ent31] | Textarea_41 [Att51] [Ent2] | Button_41 [Att55] [Ent33] | PCDATA_41 [Att0] B.ByteString deriving (Show) data Ent42 = Script_42 [Att9] [Ent2] | Ins_42 [Att23] [Ent40] | Del_42 [Att23] [Ent40] | A_42 [Att24] [Ent23] | Span_42 [Att10] [Ent39] | Bdo_42 [Att10] [Ent39] | Br_42 [Att27] | Em_42 [Att10] [Ent39] | Strong_42 [Att10] [Ent39] | Dfn_42 [Att10] [Ent39] | Code_42 [Att10] [Ent39] | Samp_42 [Att10] [Ent39] | Kbd_42 [Att10] [Ent39] | Var_42 [Att10] [Ent39] | Cite_42 [Att10] [Ent39] | Abbr_42 [Att10] [Ent39] | Acronym_42 [Att10] [Ent39] | Q_42 [Att22] [Ent39] | Tt_42 [Att10] [Ent39] | I_42 [Att10] [Ent39] | B_42 [Att10] [Ent39] | U_42 [Att10] [Ent39] | S_42 [Att10] [Ent39] | Strike_42 [Att10] [Ent39] | Input_42 [Att46] | Select_42 [Att47] [Ent31] | Textarea_42 [Att51] [Ent2] | Button_42 [Att55] [Ent33] | PCDATA_42 [Att0] B.ByteString deriving (Show) data Ent43 = Script_43 [Att9] [Ent2] | Noscript_43 [Att10] [Ent40] | Iframe_43 [Att13] [Ent40] | Div_43 [Att15] [Ent40] | P_43 [Att15] [Ent39] | H1_43 [Att15] [Ent39] | H2_43 [Att15] [Ent39] | H3_43 [Att15] [Ent39] | H4_43 [Att15] [Ent39] | H5_43 [Att15] [Ent39] | H6_43 [Att15] [Ent39] | Ul_43 [Att16] [Ent6] | Ol_43 [Att17] [Ent6] | Menu_43 [Att18] [Ent6] | Dir_43 [Att18] [Ent6] | Dl_43 [Att18] [Ent7] | Address_43 [Att10] [Ent41] | Hr_43 [Att20] | Pre_43 [Att21] [Ent42] | Blockquote_43 [Att22] [Ent40] | Center_43 [Att10] [Ent40] | Ins_43 [Att23] [Ent40] | Del_43 [Att23] [Ent40] | A_43 [Att24] [Ent23] | Span_43 [Att10] [Ent39] | Bdo_43 [Att10] [Ent39] | Br_43 [Att27] | Em_43 [Att10] [Ent39] | Strong_43 [Att10] [Ent39] | Dfn_43 [Att10] [Ent39] | Code_43 [Att10] [Ent39] | Samp_43 [Att10] [Ent39] | Kbd_43 [Att10] [Ent39] | Var_43 [Att10] [Ent39] | Cite_43 [Att10] [Ent39] | Abbr_43 [Att10] [Ent39] | Acronym_43 [Att10] [Ent39] | Q_43 [Att22] [Ent39] | Sub_43 [Att10] [Ent39] | Sup_43 [Att10] [Ent39] | Tt_43 [Att10] [Ent39] | I_43 [Att10] [Ent39] | B_43 [Att10] [Ent39] | Big_43 [Att10] [Ent39] | Small_43 [Att10] [Ent39] | U_43 [Att10] [Ent39] | S_43 [Att10] [Ent39] | Strike_43 [Att10] [Ent39] | Basefont_43 [Att28] | Font_43 [Att30] [Ent39] | Object_43 [Att31] [Ent44] | Applet_43 [Att34] [Ent44] | Img_43 [Att37] | Map_43 [Att40] [Ent36] | Input_43 [Att46] | Select_43 [Att47] [Ent31] | Textarea_43 [Att51] [Ent2] | Fieldset_43 [Att10] [Ent43] | Legend_43 [Att54] [Ent39] | Button_43 [Att55] [Ent33] | Isindex_43 [Att56] | Table_43 [Att57] [Ent16] | PCDATA_43 [Att0] B.ByteString deriving (Show) data Ent44 = Script_44 [Att9] [Ent2] | Noscript_44 [Att10] [Ent40] | Iframe_44 [Att13] [Ent40] | Div_44 [Att15] [Ent40] | P_44 [Att15] [Ent39] | H1_44 [Att15] [Ent39] | H2_44 [Att15] [Ent39] | H3_44 [Att15] [Ent39] | H4_44 [Att15] [Ent39] | H5_44 [Att15] [Ent39] | H6_44 [Att15] [Ent39] | Ul_44 [Att16] [Ent6] | Ol_44 [Att17] [Ent6] | Menu_44 [Att18] [Ent6] | Dir_44 [Att18] [Ent6] | Dl_44 [Att18] [Ent7] | Address_44 [Att10] [Ent41] | Hr_44 [Att20] | Pre_44 [Att21] [Ent42] | Blockquote_44 [Att22] [Ent40] | Center_44 [Att10] [Ent40] | Ins_44 [Att23] [Ent40] | Del_44 [Att23] [Ent40] | A_44 [Att24] [Ent23] | Span_44 [Att10] [Ent39] | Bdo_44 [Att10] [Ent39] | Br_44 [Att27] | Em_44 [Att10] [Ent39] | Strong_44 [Att10] [Ent39] | Dfn_44 [Att10] [Ent39] | Code_44 [Att10] [Ent39] | Samp_44 [Att10] [Ent39] | Kbd_44 [Att10] [Ent39] | Var_44 [Att10] [Ent39] | Cite_44 [Att10] [Ent39] | Abbr_44 [Att10] [Ent39] | Acronym_44 [Att10] [Ent39] | Q_44 [Att22] [Ent39] | Sub_44 [Att10] [Ent39] | Sup_44 [Att10] [Ent39] | Tt_44 [Att10] [Ent39] | I_44 [Att10] [Ent39] | B_44 [Att10] [Ent39] | Big_44 [Att10] [Ent39] | Small_44 [Att10] [Ent39] | U_44 [Att10] [Ent39] | S_44 [Att10] [Ent39] | Strike_44 [Att10] [Ent39] | Basefont_44 [Att28] | Font_44 [Att30] [Ent39] | Object_44 [Att31] [Ent44] | Param_44 [Att32] | Applet_44 [Att34] [Ent44] | Img_44 [Att37] | Map_44 [Att40] [Ent36] | Input_44 [Att46] | Select_44 [Att47] [Ent31] | Textarea_44 [Att51] [Ent2] | Fieldset_44 [Att10] [Ent43] | Button_44 [Att55] [Ent33] | Isindex_44 [Att56] | Table_44 [Att57] [Ent16] | PCDATA_44 [Att0] B.ByteString deriving (Show) data Ent45 = Script_45 [Att9] [Ent2] | Noscript_45 [Att10] [Ent34] | Iframe_45 [Att13] [Ent34] | Div_45 [Att15] [Ent34] | P_45 [Att15] [Ent5] | H1_45 [Att15] [Ent5] | H2_45 [Att15] [Ent5] | H3_45 [Att15] [Ent5] | H4_45 [Att15] [Ent5] | H5_45 [Att15] [Ent5] | H6_45 [Att15] [Ent5] | Ul_45 [Att16] [Ent6] | Ol_45 [Att17] [Ent6] | Menu_45 [Att18] [Ent6] | Dir_45 [Att18] [Ent6] | Dl_45 [Att18] [Ent7] | Address_45 [Att10] [Ent8] | Hr_45 [Att20] | Pre_45 [Att21] [Ent9] | Blockquote_45 [Att22] [Ent34] | Center_45 [Att10] [Ent34] | Ins_45 [Att23] [Ent34] | Del_45 [Att23] [Ent34] | A_45 [Att24] [Ent10] | Span_45 [Att10] [Ent5] | Bdo_45 [Att10] [Ent5] | Br_45 [Att27] | Em_45 [Att10] [Ent5] | Strong_45 [Att10] [Ent5] | Dfn_45 [Att10] [Ent5] | Code_45 [Att10] [Ent5] | Samp_45 [Att10] [Ent5] | Kbd_45 [Att10] [Ent5] | Var_45 [Att10] [Ent5] | Cite_45 [Att10] [Ent5] | Abbr_45 [Att10] [Ent5] | Acronym_45 [Att10] [Ent5] | Q_45 [Att22] [Ent5] | Sub_45 [Att10] [Ent5] | Sup_45 [Att10] [Ent5] | Tt_45 [Att10] [Ent5] | I_45 [Att10] [Ent5] | B_45 [Att10] [Ent5] | Big_45 [Att10] [Ent5] | Small_45 [Att10] [Ent5] | U_45 [Att10] [Ent5] | S_45 [Att10] [Ent5] | Strike_45 [Att10] [Ent5] | Basefont_45 [Att28] | Font_45 [Att30] [Ent5] | Object_45 [Att31] [Ent38] | Applet_45 [Att34] [Ent38] | Img_45 [Att37] | Map_45 [Att40] [Ent36] | Label_45 [Att45] [Ent39] | Input_45 [Att46] | Select_45 [Att47] [Ent31] | Textarea_45 [Att51] [Ent2] | Fieldset_45 [Att10] [Ent45] | Legend_45 [Att54] [Ent5] | Button_45 [Att55] [Ent33] | Isindex_45 [Att56] | Table_45 [Att57] [Ent16] | PCDATA_45 [Att0] B.ByteString deriving (Show) data Ent46 = Script_46 [Att9] [Ent2] | Noscript_46 [Att10] [Ent46] | Iframe_46 [Att13] [Ent46] | Div_46 [Att15] [Ent46] | P_46 [Att15] [Ent39] | H1_46 [Att15] [Ent39] | H2_46 [Att15] [Ent39] | H3_46 [Att15] [Ent39] | H4_46 [Att15] [Ent39] | H5_46 [Att15] [Ent39] | H6_46 [Att15] [Ent10] | Ul_46 [Att16] [Ent6] | Ol_46 [Att17] [Ent6] | Menu_46 [Att18] [Ent6] | Dir_46 [Att18] [Ent6] | Dl_46 [Att18] [Ent7] | Address_46 [Att10] [Ent41] | Hr_46 [Att20] | Pre_46 [Att21] [Ent42] | Blockquote_46 [Att22] [Ent46] | Center_46 [Att10] [Ent46] | Ins_46 [Att23] [Ent46] | Del_46 [Att23] [Ent46] | A_46 [Att24] [Ent23] | Span_46 [Att10] [Ent10] | Bdo_46 [Att10] [Ent10] | Br_46 [Att27] | Em_46 [Att10] [Ent10] | Strong_46 [Att10] [Ent10] | Dfn_46 [Att10] [Ent10] | Code_46 [Att10] [Ent10] | Samp_46 [Att10] [Ent10] | Kbd_46 [Att10] [Ent39] | Var_46 [Att10] [Ent10] | Cite_46 [Att10] [Ent39] | Abbr_46 [Att10] [Ent39] | Acronym_46 [Att10] [Ent39] | Q_46 [Att22] [Ent39] | Sub_46 [Att10] [Ent39] | Sup_46 [Att10] [Ent39] | Tt_46 [Att10] [Ent39] | I_46 [Att10] [Ent39] | B_46 [Att10] [Ent39] | Big_46 [Att10] [Ent39] | Small_46 [Att10] [Ent39] | U_46 [Att10] [Ent39] | S_46 [Att10] [Ent39] | Strike_46 [Att10] [Ent39] | Basefont_46 [Att28] | Font_46 [Att30] [Ent39] | Object_46 [Att31] [Ent48] | Applet_46 [Att34] [Ent48] | Img_46 [Att37] | Map_46 [Att40] [Ent22] | Form_46 [Att43] [Ent40] | Input_46 [Att46] | Select_46 [Att47] [Ent31] | Textarea_46 [Att51] [Ent2] | Fieldset_46 [Att10] [Ent47] | Button_46 [Att55] [Ent33] | Isindex_46 [Att56] | Table_46 [Att57] [Ent16] | PCDATA_46 [Att0] B.ByteString deriving (Show) data Ent47 = Script_47 [Att9] [Ent2] | Noscript_47 [Att10] [Ent46] | Iframe_47 [Att13] [Ent46] | Div_47 [Att15] [Ent46] | P_47 [Att15] [Ent39] | H1_47 [Att15] [Ent39] | H2_47 [Att15] [Ent39] | H3_47 [Att15] [Ent39] | H4_47 [Att15] [Ent39] | H5_47 [Att15] [Ent39] | H6_47 [Att15] [Ent10] | Ul_47 [Att16] [Ent6] | Ol_47 [Att17] [Ent6] | Menu_47 [Att18] [Ent6] | Dir_47 [Att18] [Ent6] | Dl_47 [Att18] [Ent7] | Address_47 [Att10] [Ent41] | Hr_47 [Att20] | Pre_47 [Att21] [Ent42] | Blockquote_47 [Att22] [Ent46] | Center_47 [Att10] [Ent46] | Ins_47 [Att23] [Ent46] | Del_47 [Att23] [Ent46] | A_47 [Att24] [Ent23] | Span_47 [Att10] [Ent10] | Bdo_47 [Att10] [Ent10] | Br_47 [Att27] | Em_47 [Att10] [Ent10] | Strong_47 [Att10] [Ent10] | Dfn_47 [Att10] [Ent10] | Code_47 [Att10] [Ent10] | Samp_47 [Att10] [Ent10] | Kbd_47 [Att10] [Ent39] | Var_47 [Att10] [Ent10] | Cite_47 [Att10] [Ent39] | Abbr_47 [Att10] [Ent39] | Acronym_47 [Att10] [Ent39] | Q_47 [Att22] [Ent39] | Sub_47 [Att10] [Ent39] | Sup_47 [Att10] [Ent39] | Tt_47 [Att10] [Ent39] | I_47 [Att10] [Ent39] | B_47 [Att10] [Ent39] | Big_47 [Att10] [Ent39] | Small_47 [Att10] [Ent39] | U_47 [Att10] [Ent39] | S_47 [Att10] [Ent39] | Strike_47 [Att10] [Ent39] | Basefont_47 [Att28] | Font_47 [Att30] [Ent39] | Object_47 [Att31] [Ent48] | Applet_47 [Att34] [Ent48] | Img_47 [Att37] | Map_47 [Att40] [Ent22] | Form_47 [Att43] [Ent40] | Input_47 [Att46] | Select_47 [Att47] [Ent31] | Textarea_47 [Att51] [Ent2] | Fieldset_47 [Att10] [Ent47] | Legend_47 [Att54] [Ent39] | Button_47 [Att55] [Ent33] | Isindex_47 [Att56] | Table_47 [Att57] [Ent16] | PCDATA_47 [Att0] B.ByteString deriving (Show) data Ent48 = Script_48 [Att9] [Ent2] | Noscript_48 [Att10] [Ent46] | Iframe_48 [Att13] [Ent46] | Div_48 [Att15] [Ent46] | P_48 [Att15] [Ent39] | H1_48 [Att15] [Ent39] | H2_48 [Att15] [Ent39] | H3_48 [Att15] [Ent39] | H4_48 [Att15] [Ent39] | H5_48 [Att15] [Ent39] | H6_48 [Att15] [Ent10] | Ul_48 [Att16] [Ent6] | Ol_48 [Att17] [Ent6] | Menu_48 [Att18] [Ent6] | Dir_48 [Att18] [Ent6] | Dl_48 [Att18] [Ent7] | Address_48 [Att10] [Ent41] | Hr_48 [Att20] | Pre_48 [Att21] [Ent42] | Blockquote_48 [Att22] [Ent46] | Center_48 [Att10] [Ent46] | Ins_48 [Att23] [Ent46] | Del_48 [Att23] [Ent46] | A_48 [Att24] [Ent23] | Span_48 [Att10] [Ent10] | Bdo_48 [Att10] [Ent10] | Br_48 [Att27] | Em_48 [Att10] [Ent10] | Strong_48 [Att10] [Ent10] | Dfn_48 [Att10] [Ent10] | Code_48 [Att10] [Ent10] | Samp_48 [Att10] [Ent10] | Kbd_48 [Att10] [Ent39] | Var_48 [Att10] [Ent10] | Cite_48 [Att10] [Ent39] | Abbr_48 [Att10] [Ent39] | Acronym_48 [Att10] [Ent39] | Q_48 [Att22] [Ent39] | Sub_48 [Att10] [Ent39] | Sup_48 [Att10] [Ent39] | Tt_48 [Att10] [Ent39] | I_48 [Att10] [Ent39] | B_48 [Att10] [Ent39] | Big_48 [Att10] [Ent39] | Small_48 [Att10] [Ent39] | U_48 [Att10] [Ent39] | S_48 [Att10] [Ent39] | Strike_48 [Att10] [Ent39] | Basefont_48 [Att28] | Font_48 [Att30] [Ent39] | Object_48 [Att31] [Ent48] | Param_48 [Att32] | Applet_48 [Att34] [Ent48] | Img_48 [Att37] | Map_48 [Att40] [Ent22] | Form_48 [Att43] [Ent40] | Input_48 [Att46] | Select_48 [Att47] [Ent31] | Textarea_48 [Att51] [Ent2] | Fieldset_48 [Att10] [Ent47] | Button_48 [Att55] [Ent33] | Isindex_48 [Att56] | Table_48 [Att57] [Ent16] | PCDATA_48 [Att0] B.ByteString deriving (Show) data Ent49 = Script_49 [Att9] [Ent2] | Noscript_49 [Att10] [Ent4] | Iframe_49 [Att13] [Ent4] | Div_49 [Att15] [Ent4] | P_49 [Att15] [Ent5] | H1_49 [Att15] [Ent5] | H2_49 [Att15] [Ent5] | H3_49 [Att15] [Ent5] | H4_49 [Att15] [Ent5] | H5_49 [Att15] [Ent5] | H6_49 [Att15] [Ent5] | Ul_49 [Att16] [Ent6] | Ol_49 [Att17] [Ent6] | Menu_49 [Att18] [Ent6] | Dir_49 [Att18] [Ent6] | Dl_49 [Att18] [Ent7] | Address_49 [Att10] [Ent8] | Hr_49 [Att20] | Pre_49 [Att21] [Ent9] | Blockquote_49 [Att22] [Ent4] | Center_49 [Att10] [Ent4] | Ins_49 [Att23] [Ent4] | Del_49 [Att23] [Ent4] | A_49 [Att24] [Ent10] | Span_49 [Att10] [Ent5] | Bdo_49 [Att10] [Ent5] | Br_49 [Att27] | Em_49 [Att10] [Ent5] | Strong_49 [Att10] [Ent5] | Dfn_49 [Att10] [Ent5] | Code_49 [Att10] [Ent5] | Samp_49 [Att10] [Ent5] | Kbd_49 [Att10] [Ent5] | Var_49 [Att10] [Ent5] | Cite_49 [Att10] [Ent5] | Abbr_49 [Att10] [Ent5] | Acronym_49 [Att10] [Ent5] | Q_49 [Att22] [Ent5] | Sub_49 [Att10] [Ent5] | Sup_49 [Att10] [Ent5] | Tt_49 [Att10] [Ent5] | I_49 [Att10] [Ent5] | B_49 [Att10] [Ent5] | Big_49 [Att10] [Ent5] | Small_49 [Att10] [Ent5] | U_49 [Att10] [Ent5] | S_49 [Att10] [Ent5] | Strike_49 [Att10] [Ent5] | Basefont_49 [Att28] | Font_49 [Att30] [Ent5] | Object_49 [Att31] [Ent3] | Applet_49 [Att34] [Ent3] | Img_49 [Att37] | Map_49 [Att40] [Ent22] | Form_49 [Att43] [Ent34] | Label_49 [Att45] [Ent39] | Input_49 [Att46] | Select_49 [Att47] [Ent31] | Textarea_49 [Att51] [Ent2] | Fieldset_49 [Att10] [Ent49] | Legend_49 [Att54] [Ent5] | Button_49 [Att55] [Ent33] | Isindex_49 [Att56] | Table_49 [Att57] [Ent16] | PCDATA_49 [Att0] B.ByteString deriving (Show) data Ent50 = Frameset_50 [Att11] [Ent50] | Frame_50 [Att12] | Noframes_50 [Att10] [Ent51] deriving (Show) data Ent51 = Body_51 [Att14] [Ent4] 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_ :: [Att4] -> a instance C_Meta Ent1 where _meta = Meta_1 [] meta_ = Meta_1 class C_Link a where _link :: a link_ :: [Att6] -> a instance C_Link Ent1 where _link = Link_1 [] link_ = Link_1 class C_Style a b | a -> b where _style :: [b] -> a style_ :: [Att7] -> [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_ :: [Att9] -> [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 Ent8 Ent2 where _script = Script_8 [] script_ = Script_8 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 Ent13 Ent2 where _script = Script_13 [] script_ = Script_13 instance C_Script Ent14 Ent2 where _script = Script_14 [] script_ = Script_14 instance C_Script Ent15 Ent2 where _script = Script_15 [] script_ = Script_15 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 Ent27 Ent2 where _script = Script_27 [] script_ = Script_27 instance C_Script Ent28 Ent2 where _script = Script_28 [] script_ = Script_28 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 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 instance C_Script Ent48 Ent2 where _script = Script_48 [] script_ = Script_48 instance C_Script Ent49 Ent2 where _script = Script_49 [] script_ = Script_49 class C_Noscript a b | a -> b where _noscript :: [b] -> a noscript_ :: [Att10] -> [b] -> a instance C_Noscript Ent3 Ent4 where _noscript = Noscript_3 [] noscript_ = Noscript_3 instance C_Noscript Ent4 Ent4 where _noscript = Noscript_4 [] noscript_ = Noscript_4 instance C_Noscript Ent11 Ent11 where _noscript = Noscript_11 [] noscript_ = Noscript_11 instance C_Noscript Ent14 Ent14 where _noscript = Noscript_14 [] noscript_ = Noscript_14 instance C_Noscript Ent15 Ent14 where _noscript = Noscript_15 [] noscript_ = Noscript_15 instance C_Noscript Ent20 Ent11 where _noscript = Noscript_20 [] noscript_ = Noscript_20 instance C_Noscript Ent21 Ent11 where _noscript = Noscript_21 [] noscript_ = Noscript_21 instance C_Noscript Ent22 Ent11 where _noscript = Noscript_22 [] noscript_ = Noscript_22 instance C_Noscript Ent24 Ent24 where _noscript = Noscript_24 [] noscript_ = Noscript_24 instance C_Noscript Ent27 Ent27 where _noscript = Noscript_27 [] noscript_ = Noscript_27 instance C_Noscript Ent28 Ent27 where _noscript = Noscript_28 [] noscript_ = Noscript_28 instance C_Noscript Ent29 Ent24 where _noscript = Noscript_29 [] noscript_ = Noscript_29 instance C_Noscript Ent30 Ent24 where _noscript = Noscript_30 [] noscript_ = Noscript_30 instance C_Noscript Ent33 Ent24 where _noscript = Noscript_33 [] noscript_ = Noscript_33 instance C_Noscript Ent34 Ent34 where _noscript = Noscript_34 [] noscript_ = Noscript_34 instance C_Noscript Ent35 Ent14 where _noscript = Noscript_35 [] noscript_ = Noscript_35 instance C_Noscript Ent36 Ent14 where _noscript = Noscript_36 [] noscript_ = Noscript_36 instance C_Noscript Ent37 Ent27 where _noscript = Noscript_37 [] noscript_ = Noscript_37 instance C_Noscript Ent38 Ent34 where _noscript = Noscript_38 [] noscript_ = Noscript_38 instance C_Noscript Ent40 Ent40 where _noscript = Noscript_40 [] noscript_ = Noscript_40 instance C_Noscript Ent43 Ent40 where _noscript = Noscript_43 [] noscript_ = Noscript_43 instance C_Noscript Ent44 Ent40 where _noscript = Noscript_44 [] noscript_ = Noscript_44 instance C_Noscript Ent45 Ent34 where _noscript = Noscript_45 [] noscript_ = Noscript_45 instance C_Noscript Ent46 Ent46 where _noscript = Noscript_46 [] noscript_ = Noscript_46 instance C_Noscript Ent47 Ent46 where _noscript = Noscript_47 [] noscript_ = Noscript_47 instance C_Noscript Ent48 Ent46 where _noscript = Noscript_48 [] noscript_ = Noscript_48 instance C_Noscript Ent49 Ent4 where _noscript = Noscript_49 [] noscript_ = Noscript_49 class C_Frameset a b | a -> b where _frameset :: [b] -> a frameset_ :: [Att11] -> [b] -> a instance C_Frameset Ent0 Ent50 where _frameset = Frameset_0 [] frameset_ = Frameset_0 instance C_Frameset Ent50 Ent50 where _frameset = Frameset_50 [] frameset_ = Frameset_50 class C_Frame a where _frame :: a frame_ :: [Att12] -> a instance C_Frame Ent50 where _frame = Frame_50 [] frame_ = Frame_50 class C_Iframe a b | a -> b where _iframe :: [b] -> a iframe_ :: [Att13] -> [b] -> a instance C_Iframe Ent3 Ent4 where _iframe = Iframe_3 [] iframe_ = Iframe_3 instance C_Iframe Ent4 Ent4 where _iframe = Iframe_4 [] iframe_ = Iframe_4 instance C_Iframe Ent5 Ent4 where _iframe = Iframe_5 [] iframe_ = Iframe_5 instance C_Iframe Ent8 Ent4 where _iframe = Iframe_8 [] iframe_ = Iframe_8 instance C_Iframe Ent10 Ent11 where _iframe = Iframe_10 [] iframe_ = Iframe_10 instance C_Iframe Ent11 Ent11 where _iframe = Iframe_11 [] iframe_ = Iframe_11 instance C_Iframe Ent12 Ent11 where _iframe = Iframe_12 [] iframe_ = Iframe_12 instance C_Iframe Ent14 Ent14 where _iframe = Iframe_14 [] iframe_ = Iframe_14 instance C_Iframe Ent15 Ent14 where _iframe = Iframe_15 [] iframe_ = Iframe_15 instance C_Iframe Ent20 Ent11 where _iframe = Iframe_20 [] iframe_ = Iframe_20 instance C_Iframe Ent21 Ent11 where _iframe = Iframe_21 [] iframe_ = Iframe_21 instance C_Iframe Ent23 Ent24 where _iframe = Iframe_23 [] iframe_ = Iframe_23 instance C_Iframe Ent24 Ent24 where _iframe = Iframe_24 [] iframe_ = Iframe_24 instance C_Iframe Ent25 Ent24 where _iframe = Iframe_25 [] iframe_ = Iframe_25 instance C_Iframe Ent27 Ent27 where _iframe = Iframe_27 [] iframe_ = Iframe_27 instance C_Iframe Ent28 Ent27 where _iframe = Iframe_28 [] iframe_ = Iframe_28 instance C_Iframe Ent29 Ent24 where _iframe = Iframe_29 [] iframe_ = Iframe_29 instance C_Iframe Ent30 Ent24 where _iframe = Iframe_30 [] iframe_ = Iframe_30 instance C_Iframe Ent34 Ent34 where _iframe = Iframe_34 [] iframe_ = Iframe_34 instance C_Iframe Ent35 Ent14 where _iframe = Iframe_35 [] iframe_ = Iframe_35 instance C_Iframe Ent37 Ent27 where _iframe = Iframe_37 [] iframe_ = Iframe_37 instance C_Iframe Ent38 Ent34 where _iframe = Iframe_38 [] iframe_ = Iframe_38 instance C_Iframe Ent39 Ent40 where _iframe = Iframe_39 [] iframe_ = Iframe_39 instance C_Iframe Ent40 Ent40 where _iframe = Iframe_40 [] iframe_ = Iframe_40 instance C_Iframe Ent41 Ent40 where _iframe = Iframe_41 [] iframe_ = Iframe_41 instance C_Iframe Ent43 Ent40 where _iframe = Iframe_43 [] iframe_ = Iframe_43 instance C_Iframe Ent44 Ent40 where _iframe = Iframe_44 [] iframe_ = Iframe_44 instance C_Iframe Ent45 Ent34 where _iframe = Iframe_45 [] iframe_ = Iframe_45 instance C_Iframe Ent46 Ent46 where _iframe = Iframe_46 [] iframe_ = Iframe_46 instance C_Iframe Ent47 Ent46 where _iframe = Iframe_47 [] iframe_ = Iframe_47 instance C_Iframe Ent48 Ent46 where _iframe = Iframe_48 [] iframe_ = Iframe_48 instance C_Iframe Ent49 Ent4 where _iframe = Iframe_49 [] iframe_ = Iframe_49 class C_Noframes a b | a -> b where _noframes :: [b] -> a noframes_ :: [Att10] -> [b] -> a instance C_Noframes Ent50 Ent51 where _noframes = Noframes_50 [] noframes_ = Noframes_50 class C_Body a b | a -> b where _body :: [b] -> a body_ :: [Att14] -> [b] -> a instance C_Body Ent51 Ent4 where _body = Body_51 [] body_ = Body_51 class C_Div a b | a -> b where _div :: [b] -> a div_ :: [Att15] -> [b] -> a instance C_Div Ent3 Ent4 where _div = Div_3 [] div_ = Div_3 instance C_Div Ent4 Ent4 where _div = Div_4 [] div_ = Div_4 instance C_Div Ent11 Ent11 where _div = Div_11 [] div_ = Div_11 instance C_Div Ent14 Ent14 where _div = Div_14 [] div_ = Div_14 instance C_Div Ent15 Ent14 where _div = Div_15 [] div_ = Div_15 instance C_Div Ent20 Ent11 where _div = Div_20 [] div_ = Div_20 instance C_Div Ent21 Ent11 where _div = Div_21 [] div_ = Div_21 instance C_Div Ent22 Ent11 where _div = Div_22 [] div_ = Div_22 instance C_Div Ent24 Ent24 where _div = Div_24 [] div_ = Div_24 instance C_Div Ent27 Ent27 where _div = Div_27 [] div_ = Div_27 instance C_Div Ent28 Ent27 where _div = Div_28 [] div_ = Div_28 instance C_Div Ent29 Ent24 where _div = Div_29 [] div_ = Div_29 instance C_Div Ent30 Ent24 where _div = Div_30 [] div_ = Div_30 instance C_Div Ent33 Ent24 where _div = Div_33 [] div_ = Div_33 instance C_Div Ent34 Ent34 where _div = Div_34 [] div_ = Div_34 instance C_Div Ent35 Ent14 where _div = Div_35 [] div_ = Div_35 instance C_Div Ent36 Ent14 where _div = Div_36 [] div_ = Div_36 instance C_Div Ent37 Ent27 where _div = Div_37 [] div_ = Div_37 instance C_Div Ent38 Ent34 where _div = Div_38 [] div_ = Div_38 instance C_Div Ent40 Ent40 where _div = Div_40 [] div_ = Div_40 instance C_Div Ent43 Ent40 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 Ent46 where _div = Div_46 [] div_ = Div_46 instance C_Div Ent47 Ent46 where _div = Div_47 [] div_ = Div_47 instance C_Div Ent48 Ent46 where _div = Div_48 [] div_ = Div_48 instance C_Div Ent49 Ent4 where _div = Div_49 [] div_ = Div_49 class C_P a b | a -> b where _p :: [b] -> a p_ :: [Att15] -> [b] -> a instance C_P Ent3 Ent5 where _p = P_3 [] p_ = P_3 instance C_P Ent4 Ent5 where _p = P_4 [] p_ = P_4 instance C_P Ent8 Ent5 where _p = P_8 [] p_ = P_8 instance C_P Ent11 Ent10 where _p = P_11 [] p_ = P_11 instance C_P Ent12 Ent10 where _p = P_12 [] p_ = P_12 instance C_P Ent14 Ent10 where _p = P_14 [] p_ = P_14 instance C_P Ent15 Ent10 where _p = P_15 [] p_ = P_15 instance C_P Ent20 Ent10 where _p = P_20 [] p_ = P_20 instance C_P Ent21 Ent10 where _p = P_21 [] p_ = P_21 instance C_P Ent22 Ent10 where _p = P_22 [] p_ = P_22 instance C_P Ent24 Ent23 where _p = P_24 [] p_ = P_24 instance C_P Ent25 Ent23 where _p = P_25 [] p_ = P_25 instance C_P Ent27 Ent23 where _p = P_27 [] p_ = P_27 instance C_P Ent28 Ent23 where _p = P_28 [] p_ = P_28 instance C_P Ent29 Ent23 where _p = P_29 [] p_ = P_29 instance C_P Ent30 Ent23 where _p = P_30 [] p_ = P_30 instance C_P Ent33 Ent23 where _p = P_33 [] p_ = P_33 instance C_P Ent34 Ent5 where _p = P_34 [] p_ = P_34 instance C_P Ent35 Ent10 where _p = P_35 [] p_ = P_35 instance C_P Ent36 Ent10 where _p = P_36 [] p_ = P_36 instance C_P Ent37 Ent23 where _p = P_37 [] p_ = P_37 instance C_P Ent38 Ent5 where _p = P_38 [] p_ = P_38 instance C_P Ent40 Ent39 where _p = P_40 [] p_ = P_40 instance C_P Ent41 Ent39 where _p = P_41 [] p_ = P_41 instance C_P Ent43 Ent39 where _p = P_43 [] p_ = P_43 instance C_P Ent44 Ent39 where _p = P_44 [] p_ = P_44 instance C_P Ent45 Ent5 where _p = P_45 [] p_ = P_45 instance C_P Ent46 Ent39 where _p = P_46 [] p_ = P_46 instance C_P Ent47 Ent39 where _p = P_47 [] p_ = P_47 instance C_P Ent48 Ent39 where _p = P_48 [] p_ = P_48 instance C_P Ent49 Ent5 where _p = P_49 [] p_ = P_49 class C_H1 a b | a -> b where _h1 :: [b] -> a h1_ :: [Att15] -> [b] -> a instance C_H1 Ent3 Ent5 where _h1 = H1_3 [] h1_ = H1_3 instance C_H1 Ent4 Ent5 where _h1 = H1_4 [] h1_ = H1_4 instance C_H1 Ent11 Ent10 where _h1 = H1_11 [] h1_ = H1_11 instance C_H1 Ent14 Ent10 where _h1 = H1_14 [] h1_ = H1_14 instance C_H1 Ent15 Ent10 where _h1 = H1_15 [] h1_ = H1_15 instance C_H1 Ent20 Ent10 where _h1 = H1_20 [] h1_ = H1_20 instance C_H1 Ent21 Ent10 where _h1 = H1_21 [] h1_ = H1_21 instance C_H1 Ent22 Ent10 where _h1 = H1_22 [] h1_ = H1_22 instance C_H1 Ent24 Ent23 where _h1 = H1_24 [] h1_ = H1_24 instance C_H1 Ent27 Ent23 where _h1 = H1_27 [] h1_ = H1_27 instance C_H1 Ent28 Ent23 where _h1 = H1_28 [] h1_ = H1_28 instance C_H1 Ent29 Ent23 where _h1 = H1_29 [] h1_ = H1_29 instance C_H1 Ent30 Ent23 where _h1 = H1_30 [] h1_ = H1_30 instance C_H1 Ent33 Ent23 where _h1 = H1_33 [] h1_ = H1_33 instance C_H1 Ent34 Ent5 where _h1 = H1_34 [] h1_ = H1_34 instance C_H1 Ent35 Ent10 where _h1 = H1_35 [] h1_ = H1_35 instance C_H1 Ent36 Ent10 where _h1 = H1_36 [] h1_ = H1_36 instance C_H1 Ent37 Ent23 where _h1 = H1_37 [] h1_ = H1_37 instance C_H1 Ent38 Ent5 where _h1 = H1_38 [] h1_ = H1_38 instance C_H1 Ent40 Ent39 where _h1 = H1_40 [] h1_ = H1_40 instance C_H1 Ent43 Ent39 where _h1 = H1_43 [] h1_ = H1_43 instance C_H1 Ent44 Ent39 where _h1 = H1_44 [] h1_ = H1_44 instance C_H1 Ent45 Ent5 where _h1 = H1_45 [] h1_ = H1_45 instance C_H1 Ent46 Ent39 where _h1 = H1_46 [] h1_ = H1_46 instance C_H1 Ent47 Ent39 where _h1 = H1_47 [] h1_ = H1_47 instance C_H1 Ent48 Ent39 where _h1 = H1_48 [] h1_ = H1_48 instance C_H1 Ent49 Ent5 where _h1 = H1_49 [] h1_ = H1_49 class C_H2 a b | a -> b where _h2 :: [b] -> a h2_ :: [Att15] -> [b] -> a instance C_H2 Ent3 Ent5 where _h2 = H2_3 [] h2_ = H2_3 instance C_H2 Ent4 Ent5 where _h2 = H2_4 [] h2_ = H2_4 instance C_H2 Ent11 Ent10 where _h2 = H2_11 [] h2_ = H2_11 instance C_H2 Ent14 Ent10 where _h2 = H2_14 [] h2_ = H2_14 instance C_H2 Ent15 Ent10 where _h2 = H2_15 [] h2_ = H2_15 instance C_H2 Ent20 Ent10 where _h2 = H2_20 [] h2_ = H2_20 instance C_H2 Ent21 Ent10 where _h2 = H2_21 [] h2_ = H2_21 instance C_H2 Ent22 Ent10 where _h2 = H2_22 [] h2_ = H2_22 instance C_H2 Ent24 Ent23 where _h2 = H2_24 [] h2_ = H2_24 instance C_H2 Ent27 Ent23 where _h2 = H2_27 [] h2_ = H2_27 instance C_H2 Ent28 Ent23 where _h2 = H2_28 [] h2_ = H2_28 instance C_H2 Ent29 Ent23 where _h2 = H2_29 [] h2_ = H2_29 instance C_H2 Ent30 Ent23 where _h2 = H2_30 [] h2_ = H2_30 instance C_H2 Ent33 Ent23 where _h2 = H2_33 [] h2_ = H2_33 instance C_H2 Ent34 Ent5 where _h2 = H2_34 [] h2_ = H2_34 instance C_H2 Ent35 Ent10 where _h2 = H2_35 [] h2_ = H2_35 instance C_H2 Ent36 Ent10 where _h2 = H2_36 [] h2_ = H2_36 instance C_H2 Ent37 Ent23 where _h2 = H2_37 [] h2_ = H2_37 instance C_H2 Ent38 Ent5 where _h2 = H2_38 [] h2_ = H2_38 instance C_H2 Ent40 Ent39 where _h2 = H2_40 [] h2_ = H2_40 instance C_H2 Ent43 Ent39 where _h2 = H2_43 [] h2_ = H2_43 instance C_H2 Ent44 Ent39 where _h2 = H2_44 [] h2_ = H2_44 instance C_H2 Ent45 Ent5 where _h2 = H2_45 [] h2_ = H2_45 instance C_H2 Ent46 Ent39 where _h2 = H2_46 [] h2_ = H2_46 instance C_H2 Ent47 Ent39 where _h2 = H2_47 [] h2_ = H2_47 instance C_H2 Ent48 Ent39 where _h2 = H2_48 [] h2_ = H2_48 instance C_H2 Ent49 Ent5 where _h2 = H2_49 [] h2_ = H2_49 class C_H3 a b | a -> b where _h3 :: [b] -> a h3_ :: [Att15] -> [b] -> a instance C_H3 Ent3 Ent5 where _h3 = H3_3 [] h3_ = H3_3 instance C_H3 Ent4 Ent5 where _h3 = H3_4 [] h3_ = H3_4 instance C_H3 Ent11 Ent10 where _h3 = H3_11 [] h3_ = H3_11 instance C_H3 Ent14 Ent10 where _h3 = H3_14 [] h3_ = H3_14 instance C_H3 Ent15 Ent10 where _h3 = H3_15 [] h3_ = H3_15 instance C_H3 Ent20 Ent10 where _h3 = H3_20 [] h3_ = H3_20 instance C_H3 Ent21 Ent10 where _h3 = H3_21 [] h3_ = H3_21 instance C_H3 Ent22 Ent10 where _h3 = H3_22 [] h3_ = H3_22 instance C_H3 Ent24 Ent23 where _h3 = H3_24 [] h3_ = H3_24 instance C_H3 Ent27 Ent23 where _h3 = H3_27 [] h3_ = H3_27 instance C_H3 Ent28 Ent23 where _h3 = H3_28 [] h3_ = H3_28 instance C_H3 Ent29 Ent23 where _h3 = H3_29 [] h3_ = H3_29 instance C_H3 Ent30 Ent23 where _h3 = H3_30 [] h3_ = H3_30 instance C_H3 Ent33 Ent23 where _h3 = H3_33 [] h3_ = H3_33 instance C_H3 Ent34 Ent5 where _h3 = H3_34 [] h3_ = H3_34 instance C_H3 Ent35 Ent10 where _h3 = H3_35 [] h3_ = H3_35 instance C_H3 Ent36 Ent10 where _h3 = H3_36 [] h3_ = H3_36 instance C_H3 Ent37 Ent23 where _h3 = H3_37 [] h3_ = H3_37 instance C_H3 Ent38 Ent5 where _h3 = H3_38 [] h3_ = H3_38 instance C_H3 Ent40 Ent39 where _h3 = H3_40 [] h3_ = H3_40 instance C_H3 Ent43 Ent39 where _h3 = H3_43 [] h3_ = H3_43 instance C_H3 Ent44 Ent39 where _h3 = H3_44 [] h3_ = H3_44 instance C_H3 Ent45 Ent5 where _h3 = H3_45 [] h3_ = H3_45 instance C_H3 Ent46 Ent39 where _h3 = H3_46 [] h3_ = H3_46 instance C_H3 Ent47 Ent39 where _h3 = H3_47 [] h3_ = H3_47 instance C_H3 Ent48 Ent39 where _h3 = H3_48 [] h3_ = H3_48 instance C_H3 Ent49 Ent5 where _h3 = H3_49 [] h3_ = H3_49 class C_H4 a b | a -> b where _h4 :: [b] -> a h4_ :: [Att15] -> [b] -> a instance C_H4 Ent3 Ent5 where _h4 = H4_3 [] h4_ = H4_3 instance C_H4 Ent4 Ent5 where _h4 = H4_4 [] h4_ = H4_4 instance C_H4 Ent11 Ent10 where _h4 = H4_11 [] h4_ = H4_11 instance C_H4 Ent14 Ent10 where _h4 = H4_14 [] h4_ = H4_14 instance C_H4 Ent15 Ent10 where _h4 = H4_15 [] h4_ = H4_15 instance C_H4 Ent20 Ent10 where _h4 = H4_20 [] h4_ = H4_20 instance C_H4 Ent21 Ent10 where _h4 = H4_21 [] h4_ = H4_21 instance C_H4 Ent22 Ent10 where _h4 = H4_22 [] h4_ = H4_22 instance C_H4 Ent24 Ent23 where _h4 = H4_24 [] h4_ = H4_24 instance C_H4 Ent27 Ent23 where _h4 = H4_27 [] h4_ = H4_27 instance C_H4 Ent28 Ent23 where _h4 = H4_28 [] h4_ = H4_28 instance C_H4 Ent29 Ent23 where _h4 = H4_29 [] h4_ = H4_29 instance C_H4 Ent30 Ent23 where _h4 = H4_30 [] h4_ = H4_30 instance C_H4 Ent33 Ent23 where _h4 = H4_33 [] h4_ = H4_33 instance C_H4 Ent34 Ent5 where _h4 = H4_34 [] h4_ = H4_34 instance C_H4 Ent35 Ent10 where _h4 = H4_35 [] h4_ = H4_35 instance C_H4 Ent36 Ent10 where _h4 = H4_36 [] h4_ = H4_36 instance C_H4 Ent37 Ent23 where _h4 = H4_37 [] h4_ = H4_37 instance C_H4 Ent38 Ent5 where _h4 = H4_38 [] h4_ = H4_38 instance C_H4 Ent40 Ent39 where _h4 = H4_40 [] h4_ = H4_40 instance C_H4 Ent43 Ent39 where _h4 = H4_43 [] h4_ = H4_43 instance C_H4 Ent44 Ent39 where _h4 = H4_44 [] h4_ = H4_44 instance C_H4 Ent45 Ent5 where _h4 = H4_45 [] h4_ = H4_45 instance C_H4 Ent46 Ent39 where _h4 = H4_46 [] h4_ = H4_46 instance C_H4 Ent47 Ent39 where _h4 = H4_47 [] h4_ = H4_47 instance C_H4 Ent48 Ent39 where _h4 = H4_48 [] h4_ = H4_48 instance C_H4 Ent49 Ent5 where _h4 = H4_49 [] h4_ = H4_49 class C_H5 a b | a -> b where _h5 :: [b] -> a h5_ :: [Att15] -> [b] -> a instance C_H5 Ent3 Ent5 where _h5 = H5_3 [] h5_ = H5_3 instance C_H5 Ent4 Ent5 where _h5 = H5_4 [] h5_ = H5_4 instance C_H5 Ent11 Ent10 where _h5 = H5_11 [] h5_ = H5_11 instance C_H5 Ent14 Ent10 where _h5 = H5_14 [] h5_ = H5_14 instance C_H5 Ent15 Ent10 where _h5 = H5_15 [] h5_ = H5_15 instance C_H5 Ent20 Ent10 where _h5 = H5_20 [] h5_ = H5_20 instance C_H5 Ent21 Ent10 where _h5 = H5_21 [] h5_ = H5_21 instance C_H5 Ent22 Ent10 where _h5 = H5_22 [] h5_ = H5_22 instance C_H5 Ent24 Ent23 where _h5 = H5_24 [] h5_ = H5_24 instance C_H5 Ent27 Ent23 where _h5 = H5_27 [] h5_ = H5_27 instance C_H5 Ent28 Ent23 where _h5 = H5_28 [] h5_ = H5_28 instance C_H5 Ent29 Ent23 where _h5 = H5_29 [] h5_ = H5_29 instance C_H5 Ent30 Ent23 where _h5 = H5_30 [] h5_ = H5_30 instance C_H5 Ent33 Ent23 where _h5 = H5_33 [] h5_ = H5_33 instance C_H5 Ent34 Ent5 where _h5 = H5_34 [] h5_ = H5_34 instance C_H5 Ent35 Ent10 where _h5 = H5_35 [] h5_ = H5_35 instance C_H5 Ent36 Ent10 where _h5 = H5_36 [] h5_ = H5_36 instance C_H5 Ent37 Ent23 where _h5 = H5_37 [] h5_ = H5_37 instance C_H5 Ent38 Ent5 where _h5 = H5_38 [] h5_ = H5_38 instance C_H5 Ent40 Ent39 where _h5 = H5_40 [] h5_ = H5_40 instance C_H5 Ent43 Ent39 where _h5 = H5_43 [] h5_ = H5_43 instance C_H5 Ent44 Ent39 where _h5 = H5_44 [] h5_ = H5_44 instance C_H5 Ent45 Ent5 where _h5 = H5_45 [] h5_ = H5_45 instance C_H5 Ent46 Ent39 where _h5 = H5_46 [] h5_ = H5_46 instance C_H5 Ent47 Ent39 where _h5 = H5_47 [] h5_ = H5_47 instance C_H5 Ent48 Ent39 where _h5 = H5_48 [] h5_ = H5_48 instance C_H5 Ent49 Ent5 where _h5 = H5_49 [] h5_ = H5_49 class C_H6 a b | a -> b where _h6 :: [b] -> a h6_ :: [Att15] -> [b] -> a instance C_H6 Ent3 Ent5 where _h6 = H6_3 [] h6_ = H6_3 instance C_H6 Ent4 Ent5 where _h6 = H6_4 [] h6_ = H6_4 instance C_H6 Ent11 Ent10 where _h6 = H6_11 [] h6_ = H6_11 instance C_H6 Ent14 Ent10 where _h6 = H6_14 [] h6_ = H6_14 instance C_H6 Ent15 Ent10 where _h6 = H6_15 [] h6_ = H6_15 instance C_H6 Ent20 Ent10 where _h6 = H6_20 [] h6_ = H6_20 instance C_H6 Ent21 Ent10 where _h6 = H6_21 [] h6_ = H6_21 instance C_H6 Ent22 Ent10 where _h6 = H6_22 [] h6_ = H6_22 instance C_H6 Ent24 Ent23 where _h6 = H6_24 [] h6_ = H6_24 instance C_H6 Ent27 Ent23 where _h6 = H6_27 [] h6_ = H6_27 instance C_H6 Ent28 Ent23 where _h6 = H6_28 [] h6_ = H6_28 instance C_H6 Ent29 Ent23 where _h6 = H6_29 [] h6_ = H6_29 instance C_H6 Ent30 Ent23 where _h6 = H6_30 [] h6_ = H6_30 instance C_H6 Ent33 Ent23 where _h6 = H6_33 [] h6_ = H6_33 instance C_H6 Ent34 Ent5 where _h6 = H6_34 [] h6_ = H6_34 instance C_H6 Ent35 Ent10 where _h6 = H6_35 [] h6_ = H6_35 instance C_H6 Ent36 Ent10 where _h6 = H6_36 [] h6_ = H6_36 instance C_H6 Ent37 Ent23 where _h6 = H6_37 [] h6_ = H6_37 instance C_H6 Ent38 Ent5 where _h6 = H6_38 [] h6_ = H6_38 instance C_H6 Ent40 Ent39 where _h6 = H6_40 [] h6_ = H6_40 instance C_H6 Ent43 Ent39 where _h6 = H6_43 [] h6_ = H6_43 instance C_H6 Ent44 Ent39 where _h6 = H6_44 [] h6_ = H6_44 instance C_H6 Ent45 Ent5 where _h6 = H6_45 [] h6_ = H6_45 instance C_H6 Ent46 Ent10 where _h6 = H6_46 [] h6_ = H6_46 instance C_H6 Ent47 Ent10 where _h6 = H6_47 [] h6_ = H6_47 instance C_H6 Ent48 Ent10 where _h6 = H6_48 [] h6_ = H6_48 instance C_H6 Ent49 Ent5 where _h6 = H6_49 [] h6_ = H6_49 class C_Ul a b | a -> b where _ul :: [b] -> a ul_ :: [Att16] -> [b] -> a instance C_Ul Ent3 Ent6 where _ul = Ul_3 [] ul_ = Ul_3 instance C_Ul Ent4 Ent6 where _ul = Ul_4 [] ul_ = Ul_4 instance C_Ul Ent11 Ent6 where _ul = Ul_11 [] ul_ = Ul_11 instance C_Ul Ent14 Ent6 where _ul = Ul_14 [] ul_ = Ul_14 instance C_Ul Ent15 Ent6 where _ul = Ul_15 [] ul_ = Ul_15 instance C_Ul Ent20 Ent6 where _ul = Ul_20 [] ul_ = Ul_20 instance C_Ul Ent21 Ent6 where _ul = Ul_21 [] ul_ = Ul_21 instance C_Ul Ent22 Ent6 where _ul = Ul_22 [] ul_ = Ul_22 instance C_Ul Ent24 Ent6 where _ul = Ul_24 [] ul_ = Ul_24 instance C_Ul Ent27 Ent6 where _ul = Ul_27 [] ul_ = Ul_27 instance C_Ul Ent28 Ent6 where _ul = Ul_28 [] ul_ = Ul_28 instance C_Ul Ent29 Ent6 where _ul = Ul_29 [] ul_ = Ul_29 instance C_Ul Ent30 Ent6 where _ul = Ul_30 [] ul_ = Ul_30 instance C_Ul Ent33 Ent6 where _ul = Ul_33 [] ul_ = Ul_33 instance C_Ul Ent34 Ent6 where _ul = Ul_34 [] ul_ = Ul_34 instance C_Ul Ent35 Ent6 where _ul = Ul_35 [] ul_ = Ul_35 instance C_Ul Ent36 Ent6 where _ul = Ul_36 [] ul_ = Ul_36 instance C_Ul Ent37 Ent6 where _ul = Ul_37 [] ul_ = Ul_37 instance C_Ul Ent38 Ent6 where _ul = Ul_38 [] ul_ = Ul_38 instance C_Ul Ent40 Ent6 where _ul = Ul_40 [] ul_ = Ul_40 instance C_Ul Ent43 Ent6 where _ul = Ul_43 [] ul_ = Ul_43 instance C_Ul Ent44 Ent6 where _ul = Ul_44 [] ul_ = Ul_44 instance C_Ul Ent45 Ent6 where _ul = Ul_45 [] ul_ = Ul_45 instance C_Ul Ent46 Ent6 where _ul = Ul_46 [] ul_ = Ul_46 instance C_Ul Ent47 Ent6 where _ul = Ul_47 [] ul_ = Ul_47 instance C_Ul Ent48 Ent6 where _ul = Ul_48 [] ul_ = Ul_48 instance C_Ul Ent49 Ent6 where _ul = Ul_49 [] ul_ = Ul_49 class C_Ol a b | a -> b where _ol :: [b] -> a ol_ :: [Att17] -> [b] -> a instance C_Ol Ent3 Ent6 where _ol = Ol_3 [] ol_ = Ol_3 instance C_Ol Ent4 Ent6 where _ol = Ol_4 [] ol_ = Ol_4 instance C_Ol Ent11 Ent6 where _ol = Ol_11 [] ol_ = Ol_11 instance C_Ol Ent14 Ent6 where _ol = Ol_14 [] ol_ = Ol_14 instance C_Ol Ent15 Ent6 where _ol = Ol_15 [] ol_ = Ol_15 instance C_Ol Ent20 Ent6 where _ol = Ol_20 [] ol_ = Ol_20 instance C_Ol Ent21 Ent6 where _ol = Ol_21 [] ol_ = Ol_21 instance C_Ol Ent22 Ent6 where _ol = Ol_22 [] ol_ = Ol_22 instance C_Ol Ent24 Ent6 where _ol = Ol_24 [] ol_ = Ol_24 instance C_Ol Ent27 Ent6 where _ol = Ol_27 [] ol_ = Ol_27 instance C_Ol Ent28 Ent6 where _ol = Ol_28 [] ol_ = Ol_28 instance C_Ol Ent29 Ent6 where _ol = Ol_29 [] ol_ = Ol_29 instance C_Ol Ent30 Ent6 where _ol = Ol_30 [] ol_ = Ol_30 instance C_Ol Ent33 Ent6 where _ol = Ol_33 [] ol_ = Ol_33 instance C_Ol Ent34 Ent6 where _ol = Ol_34 [] ol_ = Ol_34 instance C_Ol Ent35 Ent6 where _ol = Ol_35 [] ol_ = Ol_35 instance C_Ol Ent36 Ent6 where _ol = Ol_36 [] ol_ = Ol_36 instance C_Ol Ent37 Ent6 where _ol = Ol_37 [] ol_ = Ol_37 instance C_Ol Ent38 Ent6 where _ol = Ol_38 [] ol_ = Ol_38 instance C_Ol Ent40 Ent6 where _ol = Ol_40 [] ol_ = Ol_40 instance C_Ol Ent43 Ent6 where _ol = Ol_43 [] ol_ = Ol_43 instance C_Ol Ent44 Ent6 where _ol = Ol_44 [] ol_ = Ol_44 instance C_Ol Ent45 Ent6 where _ol = Ol_45 [] ol_ = Ol_45 instance C_Ol Ent46 Ent6 where _ol = Ol_46 [] ol_ = Ol_46 instance C_Ol Ent47 Ent6 where _ol = Ol_47 [] ol_ = Ol_47 instance C_Ol Ent48 Ent6 where _ol = Ol_48 [] ol_ = Ol_48 instance C_Ol Ent49 Ent6 where _ol = Ol_49 [] ol_ = Ol_49 class C_Menu a b | a -> b where _menu :: [b] -> a menu_ :: [Att18] -> [b] -> a instance C_Menu Ent3 Ent6 where _menu = Menu_3 [] menu_ = Menu_3 instance C_Menu Ent4 Ent6 where _menu = Menu_4 [] menu_ = Menu_4 instance C_Menu Ent11 Ent6 where _menu = Menu_11 [] menu_ = Menu_11 instance C_Menu Ent14 Ent2 where _menu = Menu_14 [] menu_ = Menu_14 instance C_Menu Ent15 Ent2 where _menu = Menu_15 [] menu_ = Menu_15 instance C_Menu Ent20 Ent6 where _menu = Menu_20 [] menu_ = Menu_20 instance C_Menu Ent21 Ent6 where _menu = Menu_21 [] menu_ = Menu_21 instance C_Menu Ent22 Ent6 where _menu = Menu_22 [] menu_ = Menu_22 instance C_Menu Ent24 Ent6 where _menu = Menu_24 [] menu_ = Menu_24 instance C_Menu Ent27 Ent6 where _menu = Menu_27 [] menu_ = Menu_27 instance C_Menu Ent28 Ent6 where _menu = Menu_28 [] menu_ = Menu_28 instance C_Menu Ent29 Ent6 where _menu = Menu_29 [] menu_ = Menu_29 instance C_Menu Ent30 Ent6 where _menu = Menu_30 [] menu_ = Menu_30 instance C_Menu Ent33 Ent6 where _menu = Menu_33 [] menu_ = Menu_33 instance C_Menu Ent34 Ent6 where _menu = Menu_34 [] menu_ = Menu_34 instance C_Menu Ent35 Ent2 where _menu = Menu_35 [] menu_ = Menu_35 instance C_Menu Ent36 Ent2 where _menu = Menu_36 [] menu_ = Menu_36 instance C_Menu Ent37 Ent6 where _menu = Menu_37 [] menu_ = Menu_37 instance C_Menu Ent38 Ent6 where _menu = Menu_38 [] menu_ = Menu_38 instance C_Menu Ent40 Ent6 where _menu = Menu_40 [] menu_ = Menu_40 instance C_Menu Ent43 Ent6 where _menu = Menu_43 [] menu_ = Menu_43 instance C_Menu Ent44 Ent6 where _menu = Menu_44 [] menu_ = Menu_44 instance C_Menu Ent45 Ent6 where _menu = Menu_45 [] menu_ = Menu_45 instance C_Menu Ent46 Ent6 where _menu = Menu_46 [] menu_ = Menu_46 instance C_Menu Ent47 Ent6 where _menu = Menu_47 [] menu_ = Menu_47 instance C_Menu Ent48 Ent6 where _menu = Menu_48 [] menu_ = Menu_48 instance C_Menu Ent49 Ent6 where _menu = Menu_49 [] menu_ = Menu_49 class C_Dir a b | a -> b where _dir :: [b] -> a dir_ :: [Att18] -> [b] -> a instance C_Dir Ent3 Ent6 where _dir = Dir_3 [] dir_ = Dir_3 instance C_Dir Ent4 Ent6 where _dir = Dir_4 [] dir_ = Dir_4 instance C_Dir Ent11 Ent6 where _dir = Dir_11 [] dir_ = Dir_11 instance C_Dir Ent14 Ent6 where _dir = Dir_14 [] dir_ = Dir_14 instance C_Dir Ent15 Ent6 where _dir = Dir_15 [] dir_ = Dir_15 instance C_Dir Ent20 Ent6 where _dir = Dir_20 [] dir_ = Dir_20 instance C_Dir Ent21 Ent6 where _dir = Dir_21 [] dir_ = Dir_21 instance C_Dir Ent22 Ent6 where _dir = Dir_22 [] dir_ = Dir_22 instance C_Dir Ent24 Ent6 where _dir = Dir_24 [] dir_ = Dir_24 instance C_Dir Ent27 Ent6 where _dir = Dir_27 [] dir_ = Dir_27 instance C_Dir Ent28 Ent6 where _dir = Dir_28 [] dir_ = Dir_28 instance C_Dir Ent29 Ent6 where _dir = Dir_29 [] dir_ = Dir_29 instance C_Dir Ent30 Ent6 where _dir = Dir_30 [] dir_ = Dir_30 instance C_Dir Ent33 Ent6 where _dir = Dir_33 [] dir_ = Dir_33 instance C_Dir Ent34 Ent6 where _dir = Dir_34 [] dir_ = Dir_34 instance C_Dir Ent35 Ent6 where _dir = Dir_35 [] dir_ = Dir_35 instance C_Dir Ent36 Ent6 where _dir = Dir_36 [] dir_ = Dir_36 instance C_Dir Ent37 Ent6 where _dir = Dir_37 [] dir_ = Dir_37 instance C_Dir Ent38 Ent6 where _dir = Dir_38 [] dir_ = Dir_38 instance C_Dir Ent40 Ent6 where _dir = Dir_40 [] dir_ = Dir_40 instance C_Dir Ent43 Ent6 where _dir = Dir_43 [] dir_ = Dir_43 instance C_Dir Ent44 Ent6 where _dir = Dir_44 [] dir_ = Dir_44 instance C_Dir Ent45 Ent6 where _dir = Dir_45 [] dir_ = Dir_45 instance C_Dir Ent46 Ent6 where _dir = Dir_46 [] dir_ = Dir_46 instance C_Dir Ent47 Ent6 where _dir = Dir_47 [] dir_ = Dir_47 instance C_Dir Ent48 Ent6 where _dir = Dir_48 [] dir_ = Dir_48 instance C_Dir Ent49 Ent6 where _dir = Dir_49 [] dir_ = Dir_49 class C_Li a b | a -> b where _li :: [b] -> a li_ :: [Att19] -> [b] -> a instance C_Li Ent6 Ent4 where _li = Li_6 [] li_ = Li_6 class C_Dl a b | a -> b where _dl :: [b] -> a dl_ :: [Att18] -> [b] -> a instance C_Dl Ent3 Ent7 where _dl = Dl_3 [] dl_ = Dl_3 instance C_Dl Ent4 Ent7 where _dl = Dl_4 [] dl_ = Dl_4 instance C_Dl Ent11 Ent7 where _dl = Dl_11 [] dl_ = Dl_11 instance C_Dl Ent14 Ent7 where _dl = Dl_14 [] dl_ = Dl_14 instance C_Dl Ent15 Ent7 where _dl = Dl_15 [] dl_ = Dl_15 instance C_Dl Ent20 Ent7 where _dl = Dl_20 [] dl_ = Dl_20 instance C_Dl Ent21 Ent7 where _dl = Dl_21 [] dl_ = Dl_21 instance C_Dl Ent22 Ent7 where _dl = Dl_22 [] dl_ = Dl_22 instance C_Dl Ent24 Ent7 where _dl = Dl_24 [] dl_ = Dl_24 instance C_Dl Ent27 Ent7 where _dl = Dl_27 [] dl_ = Dl_27 instance C_Dl Ent28 Ent7 where _dl = Dl_28 [] dl_ = Dl_28 instance C_Dl Ent29 Ent7 where _dl = Dl_29 [] dl_ = Dl_29 instance C_Dl Ent30 Ent7 where _dl = Dl_30 [] dl_ = Dl_30 instance C_Dl Ent33 Ent7 where _dl = Dl_33 [] dl_ = Dl_33 instance C_Dl Ent34 Ent7 where _dl = Dl_34 [] dl_ = Dl_34 instance C_Dl Ent35 Ent7 where _dl = Dl_35 [] dl_ = Dl_35 instance C_Dl Ent36 Ent7 where _dl = Dl_36 [] dl_ = Dl_36 instance C_Dl Ent37 Ent7 where _dl = Dl_37 [] dl_ = Dl_37 instance C_Dl Ent38 Ent7 where _dl = Dl_38 [] dl_ = Dl_38 instance C_Dl Ent40 Ent7 where _dl = Dl_40 [] dl_ = Dl_40 instance C_Dl Ent43 Ent7 where _dl = Dl_43 [] dl_ = Dl_43 instance C_Dl Ent44 Ent7 where _dl = Dl_44 [] dl_ = Dl_44 instance C_Dl Ent45 Ent7 where _dl = Dl_45 [] dl_ = Dl_45 instance C_Dl Ent46 Ent7 where _dl = Dl_46 [] dl_ = Dl_46 instance C_Dl Ent47 Ent7 where _dl = Dl_47 [] dl_ = Dl_47 instance C_Dl Ent48 Ent7 where _dl = Dl_48 [] dl_ = Dl_48 instance C_Dl Ent49 Ent7 where _dl = Dl_49 [] dl_ = Dl_49 class C_Dt a b | a -> b where _dt :: [b] -> a dt_ :: [Att10] -> [b] -> a instance C_Dt Ent7 Ent5 where _dt = Dt_7 [] dt_ = Dt_7 class C_Dd a b | a -> b where _dd :: [b] -> a dd_ :: [Att10] -> [b] -> a instance C_Dd Ent7 Ent4 where _dd = Dd_7 [] dd_ = Dd_7 class C_Address a b | a -> b where _address :: [b] -> a address_ :: [Att10] -> [b] -> a instance C_Address Ent3 Ent8 where _address = Address_3 [] address_ = Address_3 instance C_Address Ent4 Ent8 where _address = Address_4 [] address_ = Address_4 instance C_Address Ent11 Ent12 where _address = Address_11 [] address_ = Address_11 instance C_Address Ent14 Ent12 where _address = Address_14 [] address_ = Address_14 instance C_Address Ent15 Ent12 where _address = Address_15 [] address_ = Address_15 instance C_Address Ent20 Ent12 where _address = Address_20 [] address_ = Address_20 instance C_Address Ent21 Ent12 where _address = Address_21 [] address_ = Address_21 instance C_Address Ent22 Ent12 where _address = Address_22 [] address_ = Address_22 instance C_Address Ent24 Ent25 where _address = Address_24 [] address_ = Address_24 instance C_Address Ent27 Ent25 where _address = Address_27 [] address_ = Address_27 instance C_Address Ent28 Ent25 where _address = Address_28 [] address_ = Address_28 instance C_Address Ent29 Ent25 where _address = Address_29 [] address_ = Address_29 instance C_Address Ent30 Ent25 where _address = Address_30 [] address_ = Address_30 instance C_Address Ent33 Ent25 where _address = Address_33 [] address_ = Address_33 instance C_Address Ent34 Ent8 where _address = Address_34 [] address_ = Address_34 instance C_Address Ent35 Ent12 where _address = Address_35 [] address_ = Address_35 instance C_Address Ent36 Ent12 where _address = Address_36 [] address_ = Address_36 instance C_Address Ent37 Ent25 where _address = Address_37 [] address_ = Address_37 instance C_Address Ent38 Ent8 where _address = Address_38 [] address_ = Address_38 instance C_Address Ent40 Ent41 where _address = Address_40 [] address_ = Address_40 instance C_Address Ent43 Ent41 where _address = Address_43 [] address_ = Address_43 instance C_Address Ent44 Ent41 where _address = Address_44 [] address_ = Address_44 instance C_Address Ent45 Ent8 where _address = Address_45 [] address_ = Address_45 instance C_Address Ent46 Ent41 where _address = Address_46 [] address_ = Address_46 instance C_Address Ent47 Ent41 where _address = Address_47 [] address_ = Address_47 instance C_Address Ent48 Ent41 where _address = Address_48 [] address_ = Address_48 instance C_Address Ent49 Ent8 where _address = Address_49 [] address_ = Address_49 class C_Hr a where _hr :: a hr_ :: [Att20] -> a instance C_Hr Ent3 where _hr = Hr_3 [] hr_ = Hr_3 instance C_Hr Ent4 where _hr = Hr_4 [] hr_ = Hr_4 instance C_Hr Ent11 where _hr = Hr_11 [] hr_ = Hr_11 instance C_Hr Ent14 where _hr = Hr_14 [] hr_ = Hr_14 instance C_Hr Ent15 where _hr = Hr_15 [] hr_ = Hr_15 instance C_Hr Ent20 where _hr = Hr_20 [] hr_ = Hr_20 instance C_Hr Ent21 where _hr = Hr_21 [] hr_ = Hr_21 instance C_Hr Ent22 where _hr = Hr_22 [] hr_ = Hr_22 instance C_Hr Ent24 where _hr = Hr_24 [] hr_ = Hr_24 instance C_Hr Ent27 where _hr = Hr_27 [] hr_ = Hr_27 instance C_Hr Ent28 where _hr = Hr_28 [] hr_ = Hr_28 instance C_Hr Ent29 where _hr = Hr_29 [] hr_ = Hr_29 instance C_Hr Ent30 where _hr = Hr_30 [] hr_ = Hr_30 instance C_Hr Ent33 where _hr = Hr_33 [] hr_ = Hr_33 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 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 instance C_Hr Ent48 where _hr = Hr_48 [] hr_ = Hr_48 instance C_Hr Ent49 where _hr = Hr_49 [] hr_ = Hr_49 class C_Pre a b | a -> b where _pre :: [b] -> a pre_ :: [Att21] -> [b] -> a instance C_Pre Ent3 Ent9 where _pre = Pre_3 [] pre_ = Pre_3 instance C_Pre Ent4 Ent9 where _pre = Pre_4 [] pre_ = Pre_4 instance C_Pre Ent11 Ent13 where _pre = Pre_11 [] pre_ = Pre_11 instance C_Pre Ent14 Ent13 where _pre = Pre_14 [] pre_ = Pre_14 instance C_Pre Ent15 Ent13 where _pre = Pre_15 [] pre_ = Pre_15 instance C_Pre Ent20 Ent13 where _pre = Pre_20 [] pre_ = Pre_20 instance C_Pre Ent21 Ent13 where _pre = Pre_21 [] pre_ = Pre_21 instance C_Pre Ent22 Ent13 where _pre = Pre_22 [] pre_ = Pre_22 instance C_Pre Ent24 Ent26 where _pre = Pre_24 [] pre_ = Pre_24 instance C_Pre Ent27 Ent26 where _pre = Pre_27 [] pre_ = Pre_27 instance C_Pre Ent28 Ent26 where _pre = Pre_28 [] pre_ = Pre_28 instance C_Pre Ent29 Ent26 where _pre = Pre_29 [] pre_ = Pre_29 instance C_Pre Ent30 Ent26 where _pre = Pre_30 [] pre_ = Pre_30 instance C_Pre Ent33 Ent26 where _pre = Pre_33 [] pre_ = Pre_33 instance C_Pre Ent34 Ent9 where _pre = Pre_34 [] pre_ = Pre_34 instance C_Pre Ent35 Ent13 where _pre = Pre_35 [] pre_ = Pre_35 instance C_Pre Ent36 Ent13 where _pre = Pre_36 [] pre_ = Pre_36 instance C_Pre Ent37 Ent26 where _pre = Pre_37 [] pre_ = Pre_37 instance C_Pre Ent38 Ent9 where _pre = Pre_38 [] pre_ = Pre_38 instance C_Pre Ent40 Ent42 where _pre = Pre_40 [] pre_ = Pre_40 instance C_Pre Ent43 Ent42 where _pre = Pre_43 [] pre_ = Pre_43 instance C_Pre Ent44 Ent42 where _pre = Pre_44 [] pre_ = Pre_44 instance C_Pre Ent45 Ent9 where _pre = Pre_45 [] pre_ = Pre_45 instance C_Pre Ent46 Ent42 where _pre = Pre_46 [] pre_ = Pre_46 instance C_Pre Ent47 Ent42 where _pre = Pre_47 [] pre_ = Pre_47 instance C_Pre Ent48 Ent42 where _pre = Pre_48 [] pre_ = Pre_48 instance C_Pre Ent49 Ent9 where _pre = Pre_49 [] pre_ = Pre_49 class C_Blockquote a b | a -> b where _blockquote :: [b] -> a blockquote_ :: [Att22] -> [b] -> a instance C_Blockquote Ent3 Ent4 where _blockquote = Blockquote_3 [] blockquote_ = Blockquote_3 instance C_Blockquote Ent4 Ent4 where _blockquote = Blockquote_4 [] blockquote_ = Blockquote_4 instance C_Blockquote Ent11 Ent11 where _blockquote = Blockquote_11 [] blockquote_ = Blockquote_11 instance C_Blockquote Ent14 Ent14 where _blockquote = Blockquote_14 [] blockquote_ = Blockquote_14 instance C_Blockquote Ent15 Ent14 where _blockquote = Blockquote_15 [] blockquote_ = Blockquote_15 instance C_Blockquote Ent20 Ent11 where _blockquote = Blockquote_20 [] blockquote_ = Blockquote_20 instance C_Blockquote Ent21 Ent11 where _blockquote = Blockquote_21 [] blockquote_ = Blockquote_21 instance C_Blockquote Ent22 Ent11 where _blockquote = Blockquote_22 [] blockquote_ = Blockquote_22 instance C_Blockquote Ent24 Ent24 where _blockquote = Blockquote_24 [] blockquote_ = Blockquote_24 instance C_Blockquote Ent27 Ent27 where _blockquote = Blockquote_27 [] blockquote_ = Blockquote_27 instance C_Blockquote Ent28 Ent27 where _blockquote = Blockquote_28 [] blockquote_ = Blockquote_28 instance C_Blockquote Ent29 Ent24 where _blockquote = Blockquote_29 [] blockquote_ = Blockquote_29 instance C_Blockquote Ent30 Ent24 where _blockquote = Blockquote_30 [] blockquote_ = Blockquote_30 instance C_Blockquote Ent33 Ent24 where _blockquote = Blockquote_33 [] blockquote_ = Blockquote_33 instance C_Blockquote Ent34 Ent34 where _blockquote = Blockquote_34 [] blockquote_ = Blockquote_34 instance C_Blockquote Ent35 Ent14 where _blockquote = Blockquote_35 [] blockquote_ = Blockquote_35 instance C_Blockquote Ent36 Ent14 where _blockquote = Blockquote_36 [] blockquote_ = Blockquote_36 instance C_Blockquote Ent37 Ent27 where _blockquote = Blockquote_37 [] blockquote_ = Blockquote_37 instance C_Blockquote Ent38 Ent34 where _blockquote = Blockquote_38 [] blockquote_ = Blockquote_38 instance C_Blockquote Ent40 Ent40 where _blockquote = Blockquote_40 [] blockquote_ = Blockquote_40 instance C_Blockquote Ent43 Ent40 where _blockquote = Blockquote_43 [] blockquote_ = Blockquote_43 instance C_Blockquote Ent44 Ent40 where _blockquote = Blockquote_44 [] blockquote_ = Blockquote_44 instance C_Blockquote Ent45 Ent34 where _blockquote = Blockquote_45 [] blockquote_ = Blockquote_45 instance C_Blockquote Ent46 Ent46 where _blockquote = Blockquote_46 [] blockquote_ = Blockquote_46 instance C_Blockquote Ent47 Ent46 where _blockquote = Blockquote_47 [] blockquote_ = Blockquote_47 instance C_Blockquote Ent48 Ent46 where _blockquote = Blockquote_48 [] blockquote_ = Blockquote_48 instance C_Blockquote Ent49 Ent4 where _blockquote = Blockquote_49 [] blockquote_ = Blockquote_49 class C_Center a b | a -> b where _center :: [b] -> a center_ :: [Att10] -> [b] -> a instance C_Center Ent3 Ent4 where _center = Center_3 [] center_ = Center_3 instance C_Center Ent4 Ent4 where _center = Center_4 [] center_ = Center_4 instance C_Center Ent11 Ent11 where _center = Center_11 [] center_ = Center_11 instance C_Center Ent14 Ent14 where _center = Center_14 [] center_ = Center_14 instance C_Center Ent15 Ent14 where _center = Center_15 [] center_ = Center_15 instance C_Center Ent20 Ent11 where _center = Center_20 [] center_ = Center_20 instance C_Center Ent21 Ent11 where _center = Center_21 [] center_ = Center_21 instance C_Center Ent22 Ent11 where _center = Center_22 [] center_ = Center_22 instance C_Center Ent24 Ent24 where _center = Center_24 [] center_ = Center_24 instance C_Center Ent27 Ent27 where _center = Center_27 [] center_ = Center_27 instance C_Center Ent28 Ent27 where _center = Center_28 [] center_ = Center_28 instance C_Center Ent29 Ent24 where _center = Center_29 [] center_ = Center_29 instance C_Center Ent30 Ent24 where _center = Center_30 [] center_ = Center_30 instance C_Center Ent33 Ent24 where _center = Center_33 [] center_ = Center_33 instance C_Center Ent34 Ent34 where _center = Center_34 [] center_ = Center_34 instance C_Center Ent35 Ent14 where _center = Center_35 [] center_ = Center_35 instance C_Center Ent36 Ent14 where _center = Center_36 [] center_ = Center_36 instance C_Center Ent37 Ent27 where _center = Center_37 [] center_ = Center_37 instance C_Center Ent38 Ent34 where _center = Center_38 [] center_ = Center_38 instance C_Center Ent40 Ent40 where _center = Center_40 [] center_ = Center_40 instance C_Center Ent43 Ent40 where _center = Center_43 [] center_ = Center_43 instance C_Center Ent44 Ent40 where _center = Center_44 [] center_ = Center_44 instance C_Center Ent45 Ent34 where _center = Center_45 [] center_ = Center_45 instance C_Center Ent46 Ent46 where _center = Center_46 [] center_ = Center_46 instance C_Center Ent47 Ent46 where _center = Center_47 [] center_ = Center_47 instance C_Center Ent48 Ent46 where _center = Center_48 [] center_ = Center_48 instance C_Center Ent49 Ent4 where _center = Center_49 [] center_ = Center_49 class C_Ins a b | a -> b where _ins :: [b] -> a ins_ :: [Att23] -> [b] -> a instance C_Ins Ent3 Ent4 where _ins = Ins_3 [] ins_ = Ins_3 instance C_Ins Ent4 Ent4 where _ins = Ins_4 [] ins_ = Ins_4 instance C_Ins Ent5 Ent4 where _ins = Ins_5 [] ins_ = Ins_5 instance C_Ins Ent8 Ent4 where _ins = Ins_8 [] ins_ = Ins_8 instance C_Ins Ent9 Ent4 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 Ent13 Ent11 where _ins = Ins_13 [] ins_ = Ins_13 instance C_Ins Ent14 Ent14 where _ins = Ins_14 [] ins_ = Ins_14 instance C_Ins Ent15 Ent14 where _ins = Ins_15 [] ins_ = Ins_15 instance C_Ins Ent20 Ent11 where _ins = Ins_20 [] ins_ = Ins_20 instance C_Ins Ent21 Ent11 where _ins = Ins_21 [] ins_ = Ins_21 instance C_Ins Ent22 Ent11 where _ins = Ins_22 [] ins_ = Ins_22 instance C_Ins Ent23 Ent24 where _ins = Ins_23 [] ins_ = Ins_23 instance C_Ins Ent24 Ent24 where _ins = Ins_24 [] ins_ = Ins_24 instance C_Ins Ent25 Ent24 where _ins = Ins_25 [] ins_ = Ins_25 instance C_Ins Ent26 Ent24 where _ins = Ins_26 [] ins_ = Ins_26 instance C_Ins Ent27 Ent27 where _ins = Ins_27 [] ins_ = Ins_27 instance C_Ins Ent28 Ent27 where _ins = Ins_28 [] ins_ = Ins_28 instance C_Ins Ent29 Ent24 where _ins = Ins_29 [] ins_ = Ins_29 instance C_Ins Ent30 Ent24 where _ins = Ins_30 [] ins_ = Ins_30 instance C_Ins Ent33 Ent24 where _ins = Ins_33 [] ins_ = Ins_33 instance C_Ins Ent34 Ent34 where _ins = Ins_34 [] ins_ = Ins_34 instance C_Ins Ent35 Ent14 where _ins = Ins_35 [] ins_ = Ins_35 instance C_Ins Ent36 Ent14 where _ins = Ins_36 [] ins_ = Ins_36 instance C_Ins Ent37 Ent27 where _ins = Ins_37 [] ins_ = Ins_37 instance C_Ins Ent38 Ent34 where _ins = Ins_38 [] ins_ = Ins_38 instance C_Ins Ent39 Ent40 where _ins = Ins_39 [] ins_ = Ins_39 instance C_Ins Ent40 Ent40 where _ins = Ins_40 [] ins_ = Ins_40 instance C_Ins Ent41 Ent40 where _ins = Ins_41 [] ins_ = Ins_41 instance C_Ins Ent42 Ent40 where _ins = Ins_42 [] ins_ = Ins_42 instance C_Ins Ent43 Ent40 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 Ent46 where _ins = Ins_46 [] ins_ = Ins_46 instance C_Ins Ent47 Ent46 where _ins = Ins_47 [] ins_ = Ins_47 instance C_Ins Ent48 Ent46 where _ins = Ins_48 [] ins_ = Ins_48 instance C_Ins Ent49 Ent4 where _ins = Ins_49 [] ins_ = Ins_49 class C_Del a b | a -> b where _del :: [b] -> a del_ :: [Att23] -> [b] -> a instance C_Del Ent3 Ent4 where _del = Del_3 [] del_ = Del_3 instance C_Del Ent4 Ent4 where _del = Del_4 [] del_ = Del_4 instance C_Del Ent5 Ent4 where _del = Del_5 [] del_ = Del_5 instance C_Del Ent8 Ent4 where _del = Del_8 [] del_ = Del_8 instance C_Del Ent9 Ent4 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 Ent13 Ent11 where _del = Del_13 [] del_ = Del_13 instance C_Del Ent14 Ent14 where _del = Del_14 [] del_ = Del_14 instance C_Del Ent15 Ent14 where _del = Del_15 [] del_ = Del_15 instance C_Del Ent20 Ent11 where _del = Del_20 [] del_ = Del_20 instance C_Del Ent21 Ent11 where _del = Del_21 [] del_ = Del_21 instance C_Del Ent22 Ent11 where _del = Del_22 [] del_ = Del_22 instance C_Del Ent23 Ent24 where _del = Del_23 [] del_ = Del_23 instance C_Del Ent24 Ent24 where _del = Del_24 [] del_ = Del_24 instance C_Del Ent25 Ent24 where _del = Del_25 [] del_ = Del_25 instance C_Del Ent26 Ent24 where _del = Del_26 [] del_ = Del_26 instance C_Del Ent27 Ent27 where _del = Del_27 [] del_ = Del_27 instance C_Del Ent28 Ent27 where _del = Del_28 [] del_ = Del_28 instance C_Del Ent29 Ent24 where _del = Del_29 [] del_ = Del_29 instance C_Del Ent30 Ent24 where _del = Del_30 [] del_ = Del_30 instance C_Del Ent33 Ent24 where _del = Del_33 [] del_ = Del_33 instance C_Del Ent34 Ent34 where _del = Del_34 [] del_ = Del_34 instance C_Del Ent35 Ent14 where _del = Del_35 [] del_ = Del_35 instance C_Del Ent36 Ent14 where _del = Del_36 [] del_ = Del_36 instance C_Del Ent37 Ent27 where _del = Del_37 [] del_ = Del_37 instance C_Del Ent38 Ent34 where _del = Del_38 [] del_ = Del_38 instance C_Del Ent39 Ent40 where _del = Del_39 [] del_ = Del_39 instance C_Del Ent40 Ent40 where _del = Del_40 [] del_ = Del_40 instance C_Del Ent41 Ent40 where _del = Del_41 [] del_ = Del_41 instance C_Del Ent42 Ent40 where _del = Del_42 [] del_ = Del_42 instance C_Del Ent43 Ent40 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 Ent46 where _del = Del_46 [] del_ = Del_46 instance C_Del Ent47 Ent46 where _del = Del_47 [] del_ = Del_47 instance C_Del Ent48 Ent46 where _del = Del_48 [] del_ = Del_48 instance C_Del Ent49 Ent4 where _del = Del_49 [] del_ = Del_49 class C_A a b | a -> b where _a :: [b] -> a a_ :: [Att24] -> [b] -> a instance C_A Ent3 Ent10 where _a = A_3 [] a_ = A_3 instance C_A Ent4 Ent10 where _a = A_4 [] a_ = A_4 instance C_A Ent5 Ent10 where _a = A_5 [] a_ = A_5 instance C_A Ent8 Ent10 where _a = A_8 [] a_ = A_8 instance C_A Ent9 Ent10 where _a = A_9 [] a_ = A_9 instance C_A Ent34 Ent10 where _a = A_34 [] a_ = A_34 instance C_A Ent38 Ent10 where _a = A_38 [] a_ = A_38 instance C_A Ent39 Ent23 where _a = A_39 [] a_ = A_39 instance C_A Ent40 Ent23 where _a = A_40 [] a_ = A_40 instance C_A Ent41 Ent23 where _a = A_41 [] a_ = A_41 instance C_A Ent42 Ent23 where _a = A_42 [] a_ = A_42 instance C_A Ent43 Ent23 where _a = A_43 [] a_ = A_43 instance C_A Ent44 Ent23 where _a = A_44 [] a_ = A_44 instance C_A Ent45 Ent10 where _a = A_45 [] a_ = A_45 instance C_A Ent46 Ent23 where _a = A_46 [] a_ = A_46 instance C_A Ent47 Ent23 where _a = A_47 [] a_ = A_47 instance C_A Ent48 Ent23 where _a = A_48 [] a_ = A_48 instance C_A Ent49 Ent10 where _a = A_49 [] a_ = A_49 class C_Span a b | a -> b where _span :: [b] -> a span_ :: [Att10] -> [b] -> a instance C_Span Ent3 Ent5 where _span = Span_3 [] span_ = Span_3 instance C_Span Ent4 Ent5 where _span = Span_4 [] span_ = Span_4 instance C_Span Ent5 Ent5 where _span = Span_5 [] span_ = Span_5 instance C_Span Ent8 Ent5 where _span = Span_8 [] span_ = Span_8 instance C_Span Ent9 Ent5 where _span = Span_9 [] span_ = Span_9 instance C_Span Ent10 Ent10 where _span = Span_10 [] span_ = Span_10 instance C_Span Ent11 Ent10 where _span = Span_11 [] span_ = Span_11 instance C_Span Ent12 Ent10 where _span = Span_12 [] span_ = Span_12 instance C_Span Ent13 Ent10 where _span = Span_13 [] span_ = Span_13 instance C_Span Ent14 Ent10 where _span = Span_14 [] span_ = Span_14 instance C_Span Ent15 Ent10 where _span = Span_15 [] span_ = Span_15 instance C_Span Ent20 Ent10 where _span = Span_20 [] span_ = Span_20 instance C_Span Ent21 Ent10 where _span = Span_21 [] span_ = Span_21 instance C_Span Ent23 Ent23 where _span = Span_23 [] span_ = Span_23 instance C_Span Ent24 Ent23 where _span = Span_24 [] span_ = Span_24 instance C_Span Ent25 Ent23 where _span = Span_25 [] span_ = Span_25 instance C_Span Ent26 Ent23 where _span = Span_26 [] span_ = Span_26 instance C_Span Ent27 Ent23 where _span = Span_27 [] span_ = Span_27 instance C_Span Ent28 Ent23 where _span = Span_28 [] span_ = Span_28 instance C_Span Ent29 Ent23 where _span = Span_29 [] span_ = Span_29 instance C_Span Ent30 Ent23 where _span = Span_30 [] span_ = Span_30 instance C_Span Ent33 Ent23 where _span = Span_33 [] span_ = Span_33 instance C_Span Ent34 Ent5 where _span = Span_34 [] span_ = Span_34 instance C_Span Ent35 Ent10 where _span = Span_35 [] span_ = Span_35 instance C_Span Ent37 Ent23 where _span = Span_37 [] span_ = Span_37 instance C_Span Ent38 Ent5 where _span = Span_38 [] span_ = Span_38 instance C_Span Ent39 Ent39 where _span = Span_39 [] span_ = Span_39 instance C_Span Ent40 Ent39 where _span = Span_40 [] span_ = Span_40 instance C_Span Ent41 Ent39 where _span = Span_41 [] span_ = Span_41 instance C_Span Ent42 Ent39 where _span = Span_42 [] span_ = Span_42 instance C_Span Ent43 Ent39 where _span = Span_43 [] span_ = Span_43 instance C_Span Ent44 Ent39 where _span = Span_44 [] span_ = Span_44 instance C_Span Ent45 Ent5 where _span = Span_45 [] span_ = Span_45 instance C_Span Ent46 Ent10 where _span = Span_46 [] span_ = Span_46 instance C_Span Ent47 Ent10 where _span = Span_47 [] span_ = Span_47 instance C_Span Ent48 Ent10 where _span = Span_48 [] span_ = Span_48 instance C_Span Ent49 Ent5 where _span = Span_49 [] span_ = Span_49 class C_Bdo a b | a -> b where _bdo :: [b] -> a bdo_ :: [Att10] -> [b] -> a instance C_Bdo Ent3 Ent5 where _bdo = Bdo_3 [] bdo_ = Bdo_3 instance C_Bdo Ent4 Ent5 where _bdo = Bdo_4 [] bdo_ = Bdo_4 instance C_Bdo Ent5 Ent5 where _bdo = Bdo_5 [] bdo_ = Bdo_5 instance C_Bdo Ent8 Ent5 where _bdo = Bdo_8 [] bdo_ = Bdo_8 instance C_Bdo Ent9 Ent5 where _bdo = Bdo_9 [] bdo_ = Bdo_9 instance C_Bdo Ent10 Ent10 where _bdo = Bdo_10 [] bdo_ = Bdo_10 instance C_Bdo Ent11 Ent10 where _bdo = Bdo_11 [] bdo_ = Bdo_11 instance C_Bdo Ent12 Ent10 where _bdo = Bdo_12 [] bdo_ = Bdo_12 instance C_Bdo Ent13 Ent10 where _bdo = Bdo_13 [] bdo_ = Bdo_13 instance C_Bdo Ent14 Ent10 where _bdo = Bdo_14 [] bdo_ = Bdo_14 instance C_Bdo Ent15 Ent10 where _bdo = Bdo_15 [] bdo_ = Bdo_15 instance C_Bdo Ent20 Ent10 where _bdo = Bdo_20 [] bdo_ = Bdo_20 instance C_Bdo Ent21 Ent10 where _bdo = Bdo_21 [] bdo_ = Bdo_21 instance C_Bdo Ent23 Ent23 where _bdo = Bdo_23 [] bdo_ = Bdo_23 instance C_Bdo Ent24 Ent23 where _bdo = Bdo_24 [] bdo_ = Bdo_24 instance C_Bdo Ent25 Ent23 where _bdo = Bdo_25 [] bdo_ = Bdo_25 instance C_Bdo Ent26 Ent23 where _bdo = Bdo_26 [] bdo_ = Bdo_26 instance C_Bdo Ent27 Ent23 where _bdo = Bdo_27 [] bdo_ = Bdo_27 instance C_Bdo Ent28 Ent23 where _bdo = Bdo_28 [] bdo_ = Bdo_28 instance C_Bdo Ent29 Ent23 where _bdo = Bdo_29 [] bdo_ = Bdo_29 instance C_Bdo Ent30 Ent23 where _bdo = Bdo_30 [] bdo_ = Bdo_30 instance C_Bdo Ent33 Ent23 where _bdo = Bdo_33 [] bdo_ = Bdo_33 instance C_Bdo Ent34 Ent5 where _bdo = Bdo_34 [] bdo_ = Bdo_34 instance C_Bdo Ent35 Ent10 where _bdo = Bdo_35 [] bdo_ = Bdo_35 instance C_Bdo Ent37 Ent23 where _bdo = Bdo_37 [] bdo_ = Bdo_37 instance C_Bdo Ent38 Ent5 where _bdo = Bdo_38 [] bdo_ = Bdo_38 instance C_Bdo Ent39 Ent39 where _bdo = Bdo_39 [] bdo_ = Bdo_39 instance C_Bdo Ent40 Ent39 where _bdo = Bdo_40 [] bdo_ = Bdo_40 instance C_Bdo Ent41 Ent39 where _bdo = Bdo_41 [] bdo_ = Bdo_41 instance C_Bdo Ent42 Ent39 where _bdo = Bdo_42 [] bdo_ = Bdo_42 instance C_Bdo Ent43 Ent39 where _bdo = Bdo_43 [] bdo_ = Bdo_43 instance C_Bdo Ent44 Ent39 where _bdo = Bdo_44 [] bdo_ = Bdo_44 instance C_Bdo Ent45 Ent5 where _bdo = Bdo_45 [] bdo_ = Bdo_45 instance C_Bdo Ent46 Ent10 where _bdo = Bdo_46 [] bdo_ = Bdo_46 instance C_Bdo Ent47 Ent10 where _bdo = Bdo_47 [] bdo_ = Bdo_47 instance C_Bdo Ent48 Ent10 where _bdo = Bdo_48 [] bdo_ = Bdo_48 instance C_Bdo Ent49 Ent5 where _bdo = Bdo_49 [] bdo_ = Bdo_49 class C_Br a where _br :: a br_ :: [Att27] -> 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 Ent8 where _br = Br_8 [] br_ = Br_8 instance C_Br Ent9 where _br = Br_9 [] br_ = Br_9 instance C_Br Ent10 where _br = Br_10 [] br_ = Br_10 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 Ent13 where _br = Br_13 [] br_ = Br_13 instance C_Br Ent14 where _br = Br_14 [] br_ = Br_14 instance C_Br Ent15 where _br = Br_15 [] br_ = Br_15 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 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 Ent27 where _br = Br_27 [] br_ = Br_27 instance C_Br Ent28 where _br = Br_28 [] br_ = Br_28 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 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 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 Ent42 where _br = Br_42 [] br_ = Br_42 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 instance C_Br Ent48 where _br = Br_48 [] br_ = Br_48 instance C_Br Ent49 where _br = Br_49 [] br_ = Br_49 class C_Em a b | a -> b where _em :: [b] -> a em_ :: [Att10] -> [b] -> a instance C_Em Ent3 Ent5 where _em = Em_3 [] em_ = Em_3 instance C_Em Ent4 Ent5 where _em = Em_4 [] em_ = Em_4 instance C_Em Ent5 Ent5 where _em = Em_5 [] em_ = Em_5 instance C_Em Ent8 Ent5 where _em = Em_8 [] em_ = Em_8 instance C_Em Ent9 Ent5 where _em = Em_9 [] em_ = Em_9 instance C_Em Ent10 Ent10 where _em = Em_10 [] em_ = Em_10 instance C_Em Ent11 Ent10 where _em = Em_11 [] em_ = Em_11 instance C_Em Ent12 Ent10 where _em = Em_12 [] em_ = Em_12 instance C_Em Ent13 Ent10 where _em = Em_13 [] em_ = Em_13 instance C_Em Ent14 Ent10 where _em = Em_14 [] em_ = Em_14 instance C_Em Ent15 Ent10 where _em = Em_15 [] em_ = Em_15 instance C_Em Ent20 Ent10 where _em = Em_20 [] em_ = Em_20 instance C_Em Ent21 Ent10 where _em = Em_21 [] em_ = Em_21 instance C_Em Ent23 Ent23 where _em = Em_23 [] em_ = Em_23 instance C_Em Ent24 Ent23 where _em = Em_24 [] em_ = Em_24 instance C_Em Ent25 Ent23 where _em = Em_25 [] em_ = Em_25 instance C_Em Ent26 Ent23 where _em = Em_26 [] em_ = Em_26 instance C_Em Ent27 Ent23 where _em = Em_27 [] em_ = Em_27 instance C_Em Ent28 Ent23 where _em = Em_28 [] em_ = Em_28 instance C_Em Ent29 Ent23 where _em = Em_29 [] em_ = Em_29 instance C_Em Ent30 Ent23 where _em = Em_30 [] em_ = Em_30 instance C_Em Ent33 Ent23 where _em = Em_33 [] em_ = Em_33 instance C_Em Ent34 Ent5 where _em = Em_34 [] em_ = Em_34 instance C_Em Ent35 Ent10 where _em = Em_35 [] em_ = Em_35 instance C_Em Ent37 Ent23 where _em = Em_37 [] em_ = Em_37 instance C_Em Ent38 Ent5 where _em = Em_38 [] em_ = Em_38 instance C_Em Ent39 Ent39 where _em = Em_39 [] em_ = Em_39 instance C_Em Ent40 Ent39 where _em = Em_40 [] em_ = Em_40 instance C_Em Ent41 Ent39 where _em = Em_41 [] em_ = Em_41 instance C_Em Ent42 Ent39 where _em = Em_42 [] em_ = Em_42 instance C_Em Ent43 Ent39 where _em = Em_43 [] em_ = Em_43 instance C_Em Ent44 Ent39 where _em = Em_44 [] em_ = Em_44 instance C_Em Ent45 Ent5 where _em = Em_45 [] em_ = Em_45 instance C_Em Ent46 Ent10 where _em = Em_46 [] em_ = Em_46 instance C_Em Ent47 Ent10 where _em = Em_47 [] em_ = Em_47 instance C_Em Ent48 Ent10 where _em = Em_48 [] em_ = Em_48 instance C_Em Ent49 Ent5 where _em = Em_49 [] em_ = Em_49 class C_Strong a b | a -> b where _strong :: [b] -> a strong_ :: [Att10] -> [b] -> a instance C_Strong Ent3 Ent5 where _strong = Strong_3 [] strong_ = Strong_3 instance C_Strong Ent4 Ent5 where _strong = Strong_4 [] strong_ = Strong_4 instance C_Strong Ent5 Ent5 where _strong = Strong_5 [] strong_ = Strong_5 instance C_Strong Ent8 Ent5 where _strong = Strong_8 [] strong_ = Strong_8 instance C_Strong Ent9 Ent5 where _strong = Strong_9 [] strong_ = Strong_9 instance C_Strong Ent10 Ent10 where _strong = Strong_10 [] strong_ = Strong_10 instance C_Strong Ent11 Ent10 where _strong = Strong_11 [] strong_ = Strong_11 instance C_Strong Ent12 Ent10 where _strong = Strong_12 [] strong_ = Strong_12 instance C_Strong Ent13 Ent10 where _strong = Strong_13 [] strong_ = Strong_13 instance C_Strong Ent14 Ent10 where _strong = Strong_14 [] strong_ = Strong_14 instance C_Strong Ent15 Ent10 where _strong = Strong_15 [] strong_ = Strong_15 instance C_Strong Ent20 Ent10 where _strong = Strong_20 [] strong_ = Strong_20 instance C_Strong Ent21 Ent10 where _strong = Strong_21 [] strong_ = Strong_21 instance C_Strong Ent23 Ent23 where _strong = Strong_23 [] strong_ = Strong_23 instance C_Strong Ent24 Ent23 where _strong = Strong_24 [] strong_ = Strong_24 instance C_Strong Ent25 Ent23 where _strong = Strong_25 [] strong_ = Strong_25 instance C_Strong Ent26 Ent23 where _strong = Strong_26 [] strong_ = Strong_26 instance C_Strong Ent27 Ent23 where _strong = Strong_27 [] strong_ = Strong_27 instance C_Strong Ent28 Ent23 where _strong = Strong_28 [] strong_ = Strong_28 instance C_Strong Ent29 Ent23 where _strong = Strong_29 [] strong_ = Strong_29 instance C_Strong Ent30 Ent23 where _strong = Strong_30 [] strong_ = Strong_30 instance C_Strong Ent33 Ent23 where _strong = Strong_33 [] strong_ = Strong_33 instance C_Strong Ent34 Ent5 where _strong = Strong_34 [] strong_ = Strong_34 instance C_Strong Ent35 Ent10 where _strong = Strong_35 [] strong_ = Strong_35 instance C_Strong Ent37 Ent23 where _strong = Strong_37 [] strong_ = Strong_37 instance C_Strong Ent38 Ent5 where _strong = Strong_38 [] strong_ = Strong_38 instance C_Strong Ent39 Ent39 where _strong = Strong_39 [] strong_ = Strong_39 instance C_Strong Ent40 Ent39 where _strong = Strong_40 [] strong_ = Strong_40 instance C_Strong Ent41 Ent39 where _strong = Strong_41 [] strong_ = Strong_41 instance C_Strong Ent42 Ent39 where _strong = Strong_42 [] strong_ = Strong_42 instance C_Strong Ent43 Ent39 where _strong = Strong_43 [] strong_ = Strong_43 instance C_Strong Ent44 Ent39 where _strong = Strong_44 [] strong_ = Strong_44 instance C_Strong Ent45 Ent5 where _strong = Strong_45 [] strong_ = Strong_45 instance C_Strong Ent46 Ent10 where _strong = Strong_46 [] strong_ = Strong_46 instance C_Strong Ent47 Ent10 where _strong = Strong_47 [] strong_ = Strong_47 instance C_Strong Ent48 Ent10 where _strong = Strong_48 [] strong_ = Strong_48 instance C_Strong Ent49 Ent5 where _strong = Strong_49 [] strong_ = Strong_49 class C_Dfn a b | a -> b where _dfn :: [b] -> a dfn_ :: [Att10] -> [b] -> a instance C_Dfn Ent3 Ent5 where _dfn = Dfn_3 [] dfn_ = Dfn_3 instance C_Dfn Ent4 Ent5 where _dfn = Dfn_4 [] dfn_ = Dfn_4 instance C_Dfn Ent5 Ent5 where _dfn = Dfn_5 [] dfn_ = Dfn_5 instance C_Dfn Ent8 Ent5 where _dfn = Dfn_8 [] dfn_ = Dfn_8 instance C_Dfn Ent9 Ent5 where _dfn = Dfn_9 [] dfn_ = Dfn_9 instance C_Dfn Ent10 Ent10 where _dfn = Dfn_10 [] dfn_ = Dfn_10 instance C_Dfn Ent11 Ent10 where _dfn = Dfn_11 [] dfn_ = Dfn_11 instance C_Dfn Ent12 Ent10 where _dfn = Dfn_12 [] dfn_ = Dfn_12 instance C_Dfn Ent13 Ent10 where _dfn = Dfn_13 [] dfn_ = Dfn_13 instance C_Dfn Ent14 Ent10 where _dfn = Dfn_14 [] dfn_ = Dfn_14 instance C_Dfn Ent15 Ent10 where _dfn = Dfn_15 [] dfn_ = Dfn_15 instance C_Dfn Ent20 Ent10 where _dfn = Dfn_20 [] dfn_ = Dfn_20 instance C_Dfn Ent21 Ent10 where _dfn = Dfn_21 [] dfn_ = Dfn_21 instance C_Dfn Ent23 Ent23 where _dfn = Dfn_23 [] dfn_ = Dfn_23 instance C_Dfn Ent24 Ent23 where _dfn = Dfn_24 [] dfn_ = Dfn_24 instance C_Dfn Ent25 Ent23 where _dfn = Dfn_25 [] dfn_ = Dfn_25 instance C_Dfn Ent26 Ent23 where _dfn = Dfn_26 [] dfn_ = Dfn_26 instance C_Dfn Ent27 Ent23 where _dfn = Dfn_27 [] dfn_ = Dfn_27 instance C_Dfn Ent28 Ent23 where _dfn = Dfn_28 [] dfn_ = Dfn_28 instance C_Dfn Ent29 Ent23 where _dfn = Dfn_29 [] dfn_ = Dfn_29 instance C_Dfn Ent30 Ent23 where _dfn = Dfn_30 [] dfn_ = Dfn_30 instance C_Dfn Ent33 Ent23 where _dfn = Dfn_33 [] dfn_ = Dfn_33 instance C_Dfn Ent34 Ent5 where _dfn = Dfn_34 [] dfn_ = Dfn_34 instance C_Dfn Ent35 Ent10 where _dfn = Dfn_35 [] dfn_ = Dfn_35 instance C_Dfn Ent37 Ent23 where _dfn = Dfn_37 [] dfn_ = Dfn_37 instance C_Dfn Ent38 Ent5 where _dfn = Dfn_38 [] dfn_ = Dfn_38 instance C_Dfn Ent39 Ent39 where _dfn = Dfn_39 [] dfn_ = Dfn_39 instance C_Dfn Ent40 Ent39 where _dfn = Dfn_40 [] dfn_ = Dfn_40 instance C_Dfn Ent41 Ent39 where _dfn = Dfn_41 [] dfn_ = Dfn_41 instance C_Dfn Ent42 Ent39 where _dfn = Dfn_42 [] dfn_ = Dfn_42 instance C_Dfn Ent43 Ent39 where _dfn = Dfn_43 [] dfn_ = Dfn_43 instance C_Dfn Ent44 Ent39 where _dfn = Dfn_44 [] dfn_ = Dfn_44 instance C_Dfn Ent45 Ent5 where _dfn = Dfn_45 [] dfn_ = Dfn_45 instance C_Dfn Ent46 Ent10 where _dfn = Dfn_46 [] dfn_ = Dfn_46 instance C_Dfn Ent47 Ent10 where _dfn = Dfn_47 [] dfn_ = Dfn_47 instance C_Dfn Ent48 Ent10 where _dfn = Dfn_48 [] dfn_ = Dfn_48 instance C_Dfn Ent49 Ent5 where _dfn = Dfn_49 [] dfn_ = Dfn_49 class C_Code a b | a -> b where _code :: [b] -> a code_ :: [Att10] -> [b] -> a instance C_Code Ent3 Ent5 where _code = Code_3 [] code_ = Code_3 instance C_Code Ent4 Ent5 where _code = Code_4 [] code_ = Code_4 instance C_Code Ent5 Ent5 where _code = Code_5 [] code_ = Code_5 instance C_Code Ent8 Ent5 where _code = Code_8 [] code_ = Code_8 instance C_Code Ent9 Ent5 where _code = Code_9 [] code_ = Code_9 instance C_Code Ent10 Ent10 where _code = Code_10 [] code_ = Code_10 instance C_Code Ent11 Ent10 where _code = Code_11 [] code_ = Code_11 instance C_Code Ent12 Ent10 where _code = Code_12 [] code_ = Code_12 instance C_Code Ent13 Ent10 where _code = Code_13 [] code_ = Code_13 instance C_Code Ent14 Ent10 where _code = Code_14 [] code_ = Code_14 instance C_Code Ent15 Ent10 where _code = Code_15 [] code_ = Code_15 instance C_Code Ent20 Ent10 where _code = Code_20 [] code_ = Code_20 instance C_Code Ent21 Ent10 where _code = Code_21 [] code_ = Code_21 instance C_Code Ent23 Ent23 where _code = Code_23 [] code_ = Code_23 instance C_Code Ent24 Ent23 where _code = Code_24 [] code_ = Code_24 instance C_Code Ent25 Ent23 where _code = Code_25 [] code_ = Code_25 instance C_Code Ent26 Ent23 where _code = Code_26 [] code_ = Code_26 instance C_Code Ent27 Ent23 where _code = Code_27 [] code_ = Code_27 instance C_Code Ent28 Ent23 where _code = Code_28 [] code_ = Code_28 instance C_Code Ent29 Ent23 where _code = Code_29 [] code_ = Code_29 instance C_Code Ent30 Ent23 where _code = Code_30 [] code_ = Code_30 instance C_Code Ent33 Ent23 where _code = Code_33 [] code_ = Code_33 instance C_Code Ent34 Ent5 where _code = Code_34 [] code_ = Code_34 instance C_Code Ent35 Ent10 where _code = Code_35 [] code_ = Code_35 instance C_Code Ent37 Ent23 where _code = Code_37 [] code_ = Code_37 instance C_Code Ent38 Ent5 where _code = Code_38 [] code_ = Code_38 instance C_Code Ent39 Ent39 where _code = Code_39 [] code_ = Code_39 instance C_Code Ent40 Ent39 where _code = Code_40 [] code_ = Code_40 instance C_Code Ent41 Ent39 where _code = Code_41 [] code_ = Code_41 instance C_Code Ent42 Ent39 where _code = Code_42 [] code_ = Code_42 instance C_Code Ent43 Ent39 where _code = Code_43 [] code_ = Code_43 instance C_Code Ent44 Ent39 where _code = Code_44 [] code_ = Code_44 instance C_Code Ent45 Ent5 where _code = Code_45 [] code_ = Code_45 instance C_Code Ent46 Ent10 where _code = Code_46 [] code_ = Code_46 instance C_Code Ent47 Ent10 where _code = Code_47 [] code_ = Code_47 instance C_Code Ent48 Ent10 where _code = Code_48 [] code_ = Code_48 instance C_Code Ent49 Ent5 where _code = Code_49 [] code_ = Code_49 class C_Samp a b | a -> b where _samp :: [b] -> a samp_ :: [Att10] -> [b] -> a instance C_Samp Ent3 Ent5 where _samp = Samp_3 [] samp_ = Samp_3 instance C_Samp Ent4 Ent5 where _samp = Samp_4 [] samp_ = Samp_4 instance C_Samp Ent5 Ent5 where _samp = Samp_5 [] samp_ = Samp_5 instance C_Samp Ent8 Ent5 where _samp = Samp_8 [] samp_ = Samp_8 instance C_Samp Ent9 Ent5 where _samp = Samp_9 [] samp_ = Samp_9 instance C_Samp Ent10 Ent10 where _samp = Samp_10 [] samp_ = Samp_10 instance C_Samp Ent11 Ent10 where _samp = Samp_11 [] samp_ = Samp_11 instance C_Samp Ent12 Ent10 where _samp = Samp_12 [] samp_ = Samp_12 instance C_Samp Ent13 Ent10 where _samp = Samp_13 [] samp_ = Samp_13 instance C_Samp Ent14 Ent10 where _samp = Samp_14 [] samp_ = Samp_14 instance C_Samp Ent15 Ent10 where _samp = Samp_15 [] samp_ = Samp_15 instance C_Samp Ent20 Ent10 where _samp = Samp_20 [] samp_ = Samp_20 instance C_Samp Ent21 Ent10 where _samp = Samp_21 [] samp_ = Samp_21 instance C_Samp Ent23 Ent23 where _samp = Samp_23 [] samp_ = Samp_23 instance C_Samp Ent24 Ent23 where _samp = Samp_24 [] samp_ = Samp_24 instance C_Samp Ent25 Ent23 where _samp = Samp_25 [] samp_ = Samp_25 instance C_Samp Ent26 Ent23 where _samp = Samp_26 [] samp_ = Samp_26 instance C_Samp Ent27 Ent23 where _samp = Samp_27 [] samp_ = Samp_27 instance C_Samp Ent28 Ent23 where _samp = Samp_28 [] samp_ = Samp_28 instance C_Samp Ent29 Ent23 where _samp = Samp_29 [] samp_ = Samp_29 instance C_Samp Ent30 Ent23 where _samp = Samp_30 [] samp_ = Samp_30 instance C_Samp Ent33 Ent23 where _samp = Samp_33 [] samp_ = Samp_33 instance C_Samp Ent34 Ent5 where _samp = Samp_34 [] samp_ = Samp_34 instance C_Samp Ent35 Ent10 where _samp = Samp_35 [] samp_ = Samp_35 instance C_Samp Ent37 Ent23 where _samp = Samp_37 [] samp_ = Samp_37 instance C_Samp Ent38 Ent5 where _samp = Samp_38 [] samp_ = Samp_38 instance C_Samp Ent39 Ent39 where _samp = Samp_39 [] samp_ = Samp_39 instance C_Samp Ent40 Ent39 where _samp = Samp_40 [] samp_ = Samp_40 instance C_Samp Ent41 Ent39 where _samp = Samp_41 [] samp_ = Samp_41 instance C_Samp Ent42 Ent39 where _samp = Samp_42 [] samp_ = Samp_42 instance C_Samp Ent43 Ent39 where _samp = Samp_43 [] samp_ = Samp_43 instance C_Samp Ent44 Ent39 where _samp = Samp_44 [] samp_ = Samp_44 instance C_Samp Ent45 Ent5 where _samp = Samp_45 [] samp_ = Samp_45 instance C_Samp Ent46 Ent10 where _samp = Samp_46 [] samp_ = Samp_46 instance C_Samp Ent47 Ent10 where _samp = Samp_47 [] samp_ = Samp_47 instance C_Samp Ent48 Ent10 where _samp = Samp_48 [] samp_ = Samp_48 instance C_Samp Ent49 Ent5 where _samp = Samp_49 [] samp_ = Samp_49 class C_Kbd a b | a -> b where _kbd :: [b] -> a kbd_ :: [Att10] -> [b] -> a instance C_Kbd Ent3 Ent5 where _kbd = Kbd_3 [] kbd_ = Kbd_3 instance C_Kbd Ent4 Ent5 where _kbd = Kbd_4 [] kbd_ = Kbd_4 instance C_Kbd Ent5 Ent5 where _kbd = Kbd_5 [] kbd_ = Kbd_5 instance C_Kbd Ent8 Ent5 where _kbd = Kbd_8 [] kbd_ = Kbd_8 instance C_Kbd Ent9 Ent5 where _kbd = Kbd_9 [] kbd_ = Kbd_9 instance C_Kbd Ent10 Ent10 where _kbd = Kbd_10 [] kbd_ = Kbd_10 instance C_Kbd Ent11 Ent10 where _kbd = Kbd_11 [] kbd_ = Kbd_11 instance C_Kbd Ent12 Ent10 where _kbd = Kbd_12 [] kbd_ = Kbd_12 instance C_Kbd Ent13 Ent10 where _kbd = Kbd_13 [] kbd_ = Kbd_13 instance C_Kbd Ent14 Ent10 where _kbd = Kbd_14 [] kbd_ = Kbd_14 instance C_Kbd Ent15 Ent10 where _kbd = Kbd_15 [] kbd_ = Kbd_15 instance C_Kbd Ent20 Ent10 where _kbd = Kbd_20 [] kbd_ = Kbd_20 instance C_Kbd Ent21 Ent10 where _kbd = Kbd_21 [] kbd_ = Kbd_21 instance C_Kbd Ent23 Ent23 where _kbd = Kbd_23 [] kbd_ = Kbd_23 instance C_Kbd Ent24 Ent23 where _kbd = Kbd_24 [] kbd_ = Kbd_24 instance C_Kbd Ent25 Ent23 where _kbd = Kbd_25 [] kbd_ = Kbd_25 instance C_Kbd Ent26 Ent23 where _kbd = Kbd_26 [] kbd_ = Kbd_26 instance C_Kbd Ent27 Ent23 where _kbd = Kbd_27 [] kbd_ = Kbd_27 instance C_Kbd Ent28 Ent23 where _kbd = Kbd_28 [] kbd_ = Kbd_28 instance C_Kbd Ent29 Ent23 where _kbd = Kbd_29 [] kbd_ = Kbd_29 instance C_Kbd Ent30 Ent23 where _kbd = Kbd_30 [] kbd_ = Kbd_30 instance C_Kbd Ent33 Ent23 where _kbd = Kbd_33 [] kbd_ = Kbd_33 instance C_Kbd Ent34 Ent5 where _kbd = Kbd_34 [] kbd_ = Kbd_34 instance C_Kbd Ent35 Ent10 where _kbd = Kbd_35 [] kbd_ = Kbd_35 instance C_Kbd Ent37 Ent23 where _kbd = Kbd_37 [] kbd_ = Kbd_37 instance C_Kbd Ent38 Ent5 where _kbd = Kbd_38 [] kbd_ = Kbd_38 instance C_Kbd Ent39 Ent39 where _kbd = Kbd_39 [] kbd_ = Kbd_39 instance C_Kbd Ent40 Ent39 where _kbd = Kbd_40 [] kbd_ = Kbd_40 instance C_Kbd Ent41 Ent39 where _kbd = Kbd_41 [] kbd_ = Kbd_41 instance C_Kbd Ent42 Ent39 where _kbd = Kbd_42 [] kbd_ = Kbd_42 instance C_Kbd Ent43 Ent39 where _kbd = Kbd_43 [] kbd_ = Kbd_43 instance C_Kbd Ent44 Ent39 where _kbd = Kbd_44 [] kbd_ = Kbd_44 instance C_Kbd Ent45 Ent5 where _kbd = Kbd_45 [] kbd_ = Kbd_45 instance C_Kbd Ent46 Ent39 where _kbd = Kbd_46 [] kbd_ = Kbd_46 instance C_Kbd Ent47 Ent39 where _kbd = Kbd_47 [] kbd_ = Kbd_47 instance C_Kbd Ent48 Ent39 where _kbd = Kbd_48 [] kbd_ = Kbd_48 instance C_Kbd Ent49 Ent5 where _kbd = Kbd_49 [] kbd_ = Kbd_49 class C_Var a b | a -> b where _var :: [b] -> a var_ :: [Att10] -> [b] -> a instance C_Var Ent3 Ent5 where _var = Var_3 [] var_ = Var_3 instance C_Var Ent4 Ent5 where _var = Var_4 [] var_ = Var_4 instance C_Var Ent5 Ent5 where _var = Var_5 [] var_ = Var_5 instance C_Var Ent8 Ent5 where _var = Var_8 [] var_ = Var_8 instance C_Var Ent9 Ent5 where _var = Var_9 [] var_ = Var_9 instance C_Var Ent10 Ent10 where _var = Var_10 [] var_ = Var_10 instance C_Var Ent11 Ent10 where _var = Var_11 [] var_ = Var_11 instance C_Var Ent12 Ent10 where _var = Var_12 [] var_ = Var_12 instance C_Var Ent13 Ent10 where _var = Var_13 [] var_ = Var_13 instance C_Var Ent14 Ent10 where _var = Var_14 [] var_ = Var_14 instance C_Var Ent15 Ent10 where _var = Var_15 [] var_ = Var_15 instance C_Var Ent20 Ent10 where _var = Var_20 [] var_ = Var_20 instance C_Var Ent21 Ent10 where _var = Var_21 [] var_ = Var_21 instance C_Var Ent23 Ent23 where _var = Var_23 [] var_ = Var_23 instance C_Var Ent24 Ent23 where _var = Var_24 [] var_ = Var_24 instance C_Var Ent25 Ent23 where _var = Var_25 [] var_ = Var_25 instance C_Var Ent26 Ent23 where _var = Var_26 [] var_ = Var_26 instance C_Var Ent27 Ent23 where _var = Var_27 [] var_ = Var_27 instance C_Var Ent28 Ent23 where _var = Var_28 [] var_ = Var_28 instance C_Var Ent29 Ent23 where _var = Var_29 [] var_ = Var_29 instance C_Var Ent30 Ent23 where _var = Var_30 [] var_ = Var_30 instance C_Var Ent33 Ent23 where _var = Var_33 [] var_ = Var_33 instance C_Var Ent34 Ent5 where _var = Var_34 [] var_ = Var_34 instance C_Var Ent35 Ent10 where _var = Var_35 [] var_ = Var_35 instance C_Var Ent37 Ent23 where _var = Var_37 [] var_ = Var_37 instance C_Var Ent38 Ent5 where _var = Var_38 [] var_ = Var_38 instance C_Var Ent39 Ent39 where _var = Var_39 [] var_ = Var_39 instance C_Var Ent40 Ent39 where _var = Var_40 [] var_ = Var_40 instance C_Var Ent41 Ent39 where _var = Var_41 [] var_ = Var_41 instance C_Var Ent42 Ent39 where _var = Var_42 [] var_ = Var_42 instance C_Var Ent43 Ent39 where _var = Var_43 [] var_ = Var_43 instance C_Var Ent44 Ent39 where _var = Var_44 [] var_ = Var_44 instance C_Var Ent45 Ent5 where _var = Var_45 [] var_ = Var_45 instance C_Var Ent46 Ent10 where _var = Var_46 [] var_ = Var_46 instance C_Var Ent47 Ent10 where _var = Var_47 [] var_ = Var_47 instance C_Var Ent48 Ent10 where _var = Var_48 [] var_ = Var_48 instance C_Var Ent49 Ent5 where _var = Var_49 [] var_ = Var_49 class C_Cite a b | a -> b where _cite :: [b] -> a cite_ :: [Att10] -> [b] -> a instance C_Cite Ent3 Ent5 where _cite = Cite_3 [] cite_ = Cite_3 instance C_Cite Ent4 Ent5 where _cite = Cite_4 [] cite_ = Cite_4 instance C_Cite Ent5 Ent5 where _cite = Cite_5 [] cite_ = Cite_5 instance C_Cite Ent8 Ent5 where _cite = Cite_8 [] cite_ = Cite_8 instance C_Cite Ent9 Ent5 where _cite = Cite_9 [] cite_ = Cite_9 instance C_Cite Ent10 Ent10 where _cite = Cite_10 [] cite_ = Cite_10 instance C_Cite Ent11 Ent10 where _cite = Cite_11 [] cite_ = Cite_11 instance C_Cite Ent12 Ent10 where _cite = Cite_12 [] cite_ = Cite_12 instance C_Cite Ent13 Ent10 where _cite = Cite_13 [] cite_ = Cite_13 instance C_Cite Ent14 Ent10 where _cite = Cite_14 [] cite_ = Cite_14 instance C_Cite Ent15 Ent10 where _cite = Cite_15 [] cite_ = Cite_15 instance C_Cite Ent20 Ent10 where _cite = Cite_20 [] cite_ = Cite_20 instance C_Cite Ent21 Ent10 where _cite = Cite_21 [] cite_ = Cite_21 instance C_Cite Ent23 Ent23 where _cite = Cite_23 [] cite_ = Cite_23 instance C_Cite Ent24 Ent23 where _cite = Cite_24 [] cite_ = Cite_24 instance C_Cite Ent25 Ent23 where _cite = Cite_25 [] cite_ = Cite_25 instance C_Cite Ent26 Ent23 where _cite = Cite_26 [] cite_ = Cite_26 instance C_Cite Ent27 Ent23 where _cite = Cite_27 [] cite_ = Cite_27 instance C_Cite Ent28 Ent23 where _cite = Cite_28 [] cite_ = Cite_28 instance C_Cite Ent29 Ent23 where _cite = Cite_29 [] cite_ = Cite_29 instance C_Cite Ent30 Ent23 where _cite = Cite_30 [] cite_ = Cite_30 instance C_Cite Ent33 Ent23 where _cite = Cite_33 [] cite_ = Cite_33 instance C_Cite Ent34 Ent5 where _cite = Cite_34 [] cite_ = Cite_34 instance C_Cite Ent35 Ent10 where _cite = Cite_35 [] cite_ = Cite_35 instance C_Cite Ent37 Ent23 where _cite = Cite_37 [] cite_ = Cite_37 instance C_Cite Ent38 Ent5 where _cite = Cite_38 [] cite_ = Cite_38 instance C_Cite Ent39 Ent39 where _cite = Cite_39 [] cite_ = Cite_39 instance C_Cite Ent40 Ent39 where _cite = Cite_40 [] cite_ = Cite_40 instance C_Cite Ent41 Ent39 where _cite = Cite_41 [] cite_ = Cite_41 instance C_Cite Ent42 Ent39 where _cite = Cite_42 [] cite_ = Cite_42 instance C_Cite Ent43 Ent39 where _cite = Cite_43 [] cite_ = Cite_43 instance C_Cite Ent44 Ent39 where _cite = Cite_44 [] cite_ = Cite_44 instance C_Cite Ent45 Ent5 where _cite = Cite_45 [] cite_ = Cite_45 instance C_Cite Ent46 Ent39 where _cite = Cite_46 [] cite_ = Cite_46 instance C_Cite Ent47 Ent39 where _cite = Cite_47 [] cite_ = Cite_47 instance C_Cite Ent48 Ent39 where _cite = Cite_48 [] cite_ = Cite_48 instance C_Cite Ent49 Ent5 where _cite = Cite_49 [] cite_ = Cite_49 class C_Abbr a b | a -> b where _abbr :: [b] -> a abbr_ :: [Att10] -> [b] -> a instance C_Abbr Ent3 Ent5 where _abbr = Abbr_3 [] abbr_ = Abbr_3 instance C_Abbr Ent4 Ent5 where _abbr = Abbr_4 [] abbr_ = Abbr_4 instance C_Abbr Ent5 Ent5 where _abbr = Abbr_5 [] abbr_ = Abbr_5 instance C_Abbr Ent8 Ent5 where _abbr = Abbr_8 [] abbr_ = Abbr_8 instance C_Abbr Ent9 Ent5 where _abbr = Abbr_9 [] abbr_ = Abbr_9 instance C_Abbr Ent10 Ent10 where _abbr = Abbr_10 [] abbr_ = Abbr_10 instance C_Abbr Ent11 Ent10 where _abbr = Abbr_11 [] abbr_ = Abbr_11 instance C_Abbr Ent12 Ent10 where _abbr = Abbr_12 [] abbr_ = Abbr_12 instance C_Abbr Ent13 Ent10 where _abbr = Abbr_13 [] abbr_ = Abbr_13 instance C_Abbr Ent14 Ent10 where _abbr = Abbr_14 [] abbr_ = Abbr_14 instance C_Abbr Ent15 Ent10 where _abbr = Abbr_15 [] abbr_ = Abbr_15 instance C_Abbr Ent20 Ent10 where _abbr = Abbr_20 [] abbr_ = Abbr_20 instance C_Abbr Ent21 Ent10 where _abbr = Abbr_21 [] abbr_ = Abbr_21 instance C_Abbr Ent23 Ent23 where _abbr = Abbr_23 [] abbr_ = Abbr_23 instance C_Abbr Ent24 Ent23 where _abbr = Abbr_24 [] abbr_ = Abbr_24 instance C_Abbr Ent25 Ent23 where _abbr = Abbr_25 [] abbr_ = Abbr_25 instance C_Abbr Ent26 Ent23 where _abbr = Abbr_26 [] abbr_ = Abbr_26 instance C_Abbr Ent27 Ent23 where _abbr = Abbr_27 [] abbr_ = Abbr_27 instance C_Abbr Ent28 Ent23 where _abbr = Abbr_28 [] abbr_ = Abbr_28 instance C_Abbr Ent29 Ent23 where _abbr = Abbr_29 [] abbr_ = Abbr_29 instance C_Abbr Ent30 Ent23 where _abbr = Abbr_30 [] abbr_ = Abbr_30 instance C_Abbr Ent33 Ent23 where _abbr = Abbr_33 [] abbr_ = Abbr_33 instance C_Abbr Ent34 Ent5 where _abbr = Abbr_34 [] abbr_ = Abbr_34 instance C_Abbr Ent35 Ent10 where _abbr = Abbr_35 [] abbr_ = Abbr_35 instance C_Abbr Ent37 Ent23 where _abbr = Abbr_37 [] abbr_ = Abbr_37 instance C_Abbr Ent38 Ent5 where _abbr = Abbr_38 [] abbr_ = Abbr_38 instance C_Abbr Ent39 Ent39 where _abbr = Abbr_39 [] abbr_ = Abbr_39 instance C_Abbr Ent40 Ent39 where _abbr = Abbr_40 [] abbr_ = Abbr_40 instance C_Abbr Ent41 Ent39 where _abbr = Abbr_41 [] abbr_ = Abbr_41 instance C_Abbr Ent42 Ent39 where _abbr = Abbr_42 [] abbr_ = Abbr_42 instance C_Abbr Ent43 Ent39 where _abbr = Abbr_43 [] abbr_ = Abbr_43 instance C_Abbr Ent44 Ent39 where _abbr = Abbr_44 [] abbr_ = Abbr_44 instance C_Abbr Ent45 Ent5 where _abbr = Abbr_45 [] abbr_ = Abbr_45 instance C_Abbr Ent46 Ent39 where _abbr = Abbr_46 [] abbr_ = Abbr_46 instance C_Abbr Ent47 Ent39 where _abbr = Abbr_47 [] abbr_ = Abbr_47 instance C_Abbr Ent48 Ent39 where _abbr = Abbr_48 [] abbr_ = Abbr_48 instance C_Abbr Ent49 Ent5 where _abbr = Abbr_49 [] abbr_ = Abbr_49 class C_Acronym a b | a -> b where _acronym :: [b] -> a acronym_ :: [Att10] -> [b] -> a instance C_Acronym Ent3 Ent5 where _acronym = Acronym_3 [] acronym_ = Acronym_3 instance C_Acronym Ent4 Ent5 where _acronym = Acronym_4 [] acronym_ = Acronym_4 instance C_Acronym Ent5 Ent5 where _acronym = Acronym_5 [] acronym_ = Acronym_5 instance C_Acronym Ent8 Ent5 where _acronym = Acronym_8 [] acronym_ = Acronym_8 instance C_Acronym Ent9 Ent5 where _acronym = Acronym_9 [] acronym_ = Acronym_9 instance C_Acronym Ent10 Ent10 where _acronym = Acronym_10 [] acronym_ = Acronym_10 instance C_Acronym Ent11 Ent10 where _acronym = Acronym_11 [] acronym_ = Acronym_11 instance C_Acronym Ent12 Ent10 where _acronym = Acronym_12 [] acronym_ = Acronym_12 instance C_Acronym Ent13 Ent10 where _acronym = Acronym_13 [] acronym_ = Acronym_13 instance C_Acronym Ent14 Ent10 where _acronym = Acronym_14 [] acronym_ = Acronym_14 instance C_Acronym Ent15 Ent10 where _acronym = Acronym_15 [] acronym_ = Acronym_15 instance C_Acronym Ent20 Ent10 where _acronym = Acronym_20 [] acronym_ = Acronym_20 instance C_Acronym Ent21 Ent10 where _acronym = Acronym_21 [] acronym_ = Acronym_21 instance C_Acronym Ent23 Ent23 where _acronym = Acronym_23 [] acronym_ = Acronym_23 instance C_Acronym Ent24 Ent23 where _acronym = Acronym_24 [] acronym_ = Acronym_24 instance C_Acronym Ent25 Ent23 where _acronym = Acronym_25 [] acronym_ = Acronym_25 instance C_Acronym Ent26 Ent23 where _acronym = Acronym_26 [] acronym_ = Acronym_26 instance C_Acronym Ent27 Ent23 where _acronym = Acronym_27 [] acronym_ = Acronym_27 instance C_Acronym Ent28 Ent23 where _acronym = Acronym_28 [] acronym_ = Acronym_28 instance C_Acronym Ent29 Ent23 where _acronym = Acronym_29 [] acronym_ = Acronym_29 instance C_Acronym Ent30 Ent23 where _acronym = Acronym_30 [] acronym_ = Acronym_30 instance C_Acronym Ent33 Ent23 where _acronym = Acronym_33 [] acronym_ = Acronym_33 instance C_Acronym Ent34 Ent5 where _acronym = Acronym_34 [] acronym_ = Acronym_34 instance C_Acronym Ent35 Ent10 where _acronym = Acronym_35 [] acronym_ = Acronym_35 instance C_Acronym Ent37 Ent23 where _acronym = Acronym_37 [] acronym_ = Acronym_37 instance C_Acronym Ent38 Ent5 where _acronym = Acronym_38 [] acronym_ = Acronym_38 instance C_Acronym Ent39 Ent39 where _acronym = Acronym_39 [] acronym_ = Acronym_39 instance C_Acronym Ent40 Ent39 where _acronym = Acronym_40 [] acronym_ = Acronym_40 instance C_Acronym Ent41 Ent39 where _acronym = Acronym_41 [] acronym_ = Acronym_41 instance C_Acronym Ent42 Ent39 where _acronym = Acronym_42 [] acronym_ = Acronym_42 instance C_Acronym Ent43 Ent39 where _acronym = Acronym_43 [] acronym_ = Acronym_43 instance C_Acronym Ent44 Ent39 where _acronym = Acronym_44 [] acronym_ = Acronym_44 instance C_Acronym Ent45 Ent5 where _acronym = Acronym_45 [] acronym_ = Acronym_45 instance C_Acronym Ent46 Ent39 where _acronym = Acronym_46 [] acronym_ = Acronym_46 instance C_Acronym Ent47 Ent39 where _acronym = Acronym_47 [] acronym_ = Acronym_47 instance C_Acronym Ent48 Ent39 where _acronym = Acronym_48 [] acronym_ = Acronym_48 instance C_Acronym Ent49 Ent5 where _acronym = Acronym_49 [] acronym_ = Acronym_49 class C_Q a b | a -> b where _q :: [b] -> a q_ :: [Att22] -> [b] -> a instance C_Q Ent3 Ent5 where _q = Q_3 [] q_ = Q_3 instance C_Q Ent4 Ent5 where _q = Q_4 [] q_ = Q_4 instance C_Q Ent5 Ent5 where _q = Q_5 [] q_ = Q_5 instance C_Q Ent8 Ent5 where _q = Q_8 [] q_ = Q_8 instance C_Q Ent9 Ent5 where _q = Q_9 [] q_ = Q_9 instance C_Q Ent10 Ent10 where _q = Q_10 [] q_ = Q_10 instance C_Q Ent11 Ent10 where _q = Q_11 [] q_ = Q_11 instance C_Q Ent12 Ent10 where _q = Q_12 [] q_ = Q_12 instance C_Q Ent13 Ent10 where _q = Q_13 [] q_ = Q_13 instance C_Q Ent14 Ent10 where _q = Q_14 [] q_ = Q_14 instance C_Q Ent15 Ent10 where _q = Q_15 [] q_ = Q_15 instance C_Q Ent20 Ent10 where _q = Q_20 [] q_ = Q_20 instance C_Q Ent21 Ent10 where _q = Q_21 [] q_ = Q_21 instance C_Q Ent23 Ent23 where _q = Q_23 [] q_ = Q_23 instance C_Q Ent24 Ent23 where _q = Q_24 [] q_ = Q_24 instance C_Q Ent25 Ent23 where _q = Q_25 [] q_ = Q_25 instance C_Q Ent26 Ent23 where _q = Q_26 [] q_ = Q_26 instance C_Q Ent27 Ent23 where _q = Q_27 [] q_ = Q_27 instance C_Q Ent28 Ent23 where _q = Q_28 [] q_ = Q_28 instance C_Q Ent29 Ent23 where _q = Q_29 [] q_ = Q_29 instance C_Q Ent30 Ent23 where _q = Q_30 [] q_ = Q_30 instance C_Q Ent33 Ent23 where _q = Q_33 [] q_ = Q_33 instance C_Q Ent34 Ent5 where _q = Q_34 [] q_ = Q_34 instance C_Q Ent35 Ent10 where _q = Q_35 [] q_ = Q_35 instance C_Q Ent37 Ent23 where _q = Q_37 [] q_ = Q_37 instance C_Q Ent38 Ent5 where _q = Q_38 [] q_ = Q_38 instance C_Q Ent39 Ent39 where _q = Q_39 [] q_ = Q_39 instance C_Q Ent40 Ent39 where _q = Q_40 [] q_ = Q_40 instance C_Q Ent41 Ent39 where _q = Q_41 [] q_ = Q_41 instance C_Q Ent42 Ent39 where _q = Q_42 [] q_ = Q_42 instance C_Q Ent43 Ent39 where _q = Q_43 [] q_ = Q_43 instance C_Q Ent44 Ent39 where _q = Q_44 [] q_ = Q_44 instance C_Q Ent45 Ent5 where _q = Q_45 [] q_ = Q_45 instance C_Q Ent46 Ent39 where _q = Q_46 [] q_ = Q_46 instance C_Q Ent47 Ent39 where _q = Q_47 [] q_ = Q_47 instance C_Q Ent48 Ent39 where _q = Q_48 [] q_ = Q_48 instance C_Q Ent49 Ent5 where _q = Q_49 [] q_ = Q_49 class C_Sub a b | a -> b where _sub :: [b] -> a sub_ :: [Att10] -> [b] -> a instance C_Sub Ent3 Ent5 where _sub = Sub_3 [] sub_ = Sub_3 instance C_Sub Ent4 Ent5 where _sub = Sub_4 [] sub_ = Sub_4 instance C_Sub Ent5 Ent5 where _sub = Sub_5 [] sub_ = Sub_5 instance C_Sub Ent8 Ent5 where _sub = Sub_8 [] sub_ = Sub_8 instance C_Sub Ent10 Ent10 where _sub = Sub_10 [] sub_ = Sub_10 instance C_Sub Ent11 Ent10 where _sub = Sub_11 [] sub_ = Sub_11 instance C_Sub Ent12 Ent10 where _sub = Sub_12 [] sub_ = Sub_12 instance C_Sub Ent14 Ent10 where _sub = Sub_14 [] sub_ = Sub_14 instance C_Sub Ent15 Ent10 where _sub = Sub_15 [] sub_ = Sub_15 instance C_Sub Ent20 Ent10 where _sub = Sub_20 [] sub_ = Sub_20 instance C_Sub Ent21 Ent10 where _sub = Sub_21 [] sub_ = Sub_21 instance C_Sub Ent23 Ent23 where _sub = Sub_23 [] sub_ = Sub_23 instance C_Sub Ent24 Ent23 where _sub = Sub_24 [] sub_ = Sub_24 instance C_Sub Ent25 Ent23 where _sub = Sub_25 [] sub_ = Sub_25 instance C_Sub Ent27 Ent23 where _sub = Sub_27 [] sub_ = Sub_27 instance C_Sub Ent28 Ent23 where _sub = Sub_28 [] sub_ = Sub_28 instance C_Sub Ent29 Ent23 where _sub = Sub_29 [] sub_ = Sub_29 instance C_Sub Ent30 Ent23 where _sub = Sub_30 [] sub_ = Sub_30 instance C_Sub Ent33 Ent23 where _sub = Sub_33 [] sub_ = Sub_33 instance C_Sub Ent34 Ent5 where _sub = Sub_34 [] sub_ = Sub_34 instance C_Sub Ent35 Ent10 where _sub = Sub_35 [] sub_ = Sub_35 instance C_Sub Ent37 Ent23 where _sub = Sub_37 [] sub_ = Sub_37 instance C_Sub Ent38 Ent5 where _sub = Sub_38 [] sub_ = Sub_38 instance C_Sub Ent39 Ent39 where _sub = Sub_39 [] sub_ = Sub_39 instance C_Sub Ent40 Ent39 where _sub = Sub_40 [] sub_ = Sub_40 instance C_Sub Ent41 Ent39 where _sub = Sub_41 [] sub_ = Sub_41 instance C_Sub Ent43 Ent39 where _sub = Sub_43 [] sub_ = Sub_43 instance C_Sub Ent44 Ent39 where _sub = Sub_44 [] sub_ = Sub_44 instance C_Sub Ent45 Ent5 where _sub = Sub_45 [] sub_ = Sub_45 instance C_Sub Ent46 Ent39 where _sub = Sub_46 [] sub_ = Sub_46 instance C_Sub Ent47 Ent39 where _sub = Sub_47 [] sub_ = Sub_47 instance C_Sub Ent48 Ent39 where _sub = Sub_48 [] sub_ = Sub_48 instance C_Sub Ent49 Ent5 where _sub = Sub_49 [] sub_ = Sub_49 class C_Sup a b | a -> b where _sup :: [b] -> a sup_ :: [Att10] -> [b] -> a instance C_Sup Ent3 Ent5 where _sup = Sup_3 [] sup_ = Sup_3 instance C_Sup Ent4 Ent5 where _sup = Sup_4 [] sup_ = Sup_4 instance C_Sup Ent5 Ent5 where _sup = Sup_5 [] sup_ = Sup_5 instance C_Sup Ent8 Ent5 where _sup = Sup_8 [] sup_ = Sup_8 instance C_Sup Ent10 Ent10 where _sup = Sup_10 [] sup_ = Sup_10 instance C_Sup Ent11 Ent10 where _sup = Sup_11 [] sup_ = Sup_11 instance C_Sup Ent12 Ent10 where _sup = Sup_12 [] sup_ = Sup_12 instance C_Sup Ent14 Ent10 where _sup = Sup_14 [] sup_ = Sup_14 instance C_Sup Ent15 Ent10 where _sup = Sup_15 [] sup_ = Sup_15 instance C_Sup Ent20 Ent10 where _sup = Sup_20 [] sup_ = Sup_20 instance C_Sup Ent21 Ent10 where _sup = Sup_21 [] sup_ = Sup_21 instance C_Sup Ent23 Ent23 where _sup = Sup_23 [] sup_ = Sup_23 instance C_Sup Ent24 Ent23 where _sup = Sup_24 [] sup_ = Sup_24 instance C_Sup Ent25 Ent23 where _sup = Sup_25 [] sup_ = Sup_25 instance C_Sup Ent27 Ent23 where _sup = Sup_27 [] sup_ = Sup_27 instance C_Sup Ent28 Ent23 where _sup = Sup_28 [] sup_ = Sup_28 instance C_Sup Ent29 Ent23 where _sup = Sup_29 [] sup_ = Sup_29 instance C_Sup Ent30 Ent23 where _sup = Sup_30 [] sup_ = Sup_30 instance C_Sup Ent33 Ent23 where _sup = Sup_33 [] sup_ = Sup_33 instance C_Sup Ent34 Ent5 where _sup = Sup_34 [] sup_ = Sup_34 instance C_Sup Ent35 Ent10 where _sup = Sup_35 [] sup_ = Sup_35 instance C_Sup Ent37 Ent23 where _sup = Sup_37 [] sup_ = Sup_37 instance C_Sup Ent38 Ent5 where _sup = Sup_38 [] sup_ = Sup_38 instance C_Sup Ent39 Ent39 where _sup = Sup_39 [] sup_ = Sup_39 instance C_Sup Ent40 Ent39 where _sup = Sup_40 [] sup_ = Sup_40 instance C_Sup Ent41 Ent39 where _sup = Sup_41 [] sup_ = Sup_41 instance C_Sup Ent43 Ent39 where _sup = Sup_43 [] sup_ = Sup_43 instance C_Sup Ent44 Ent39 where _sup = Sup_44 [] sup_ = Sup_44 instance C_Sup Ent45 Ent5 where _sup = Sup_45 [] sup_ = Sup_45 instance C_Sup Ent46 Ent39 where _sup = Sup_46 [] sup_ = Sup_46 instance C_Sup Ent47 Ent39 where _sup = Sup_47 [] sup_ = Sup_47 instance C_Sup Ent48 Ent39 where _sup = Sup_48 [] sup_ = Sup_48 instance C_Sup Ent49 Ent5 where _sup = Sup_49 [] sup_ = Sup_49 class C_Tt a b | a -> b where _tt :: [b] -> a tt_ :: [Att10] -> [b] -> a instance C_Tt Ent3 Ent5 where _tt = Tt_3 [] tt_ = Tt_3 instance C_Tt Ent4 Ent5 where _tt = Tt_4 [] tt_ = Tt_4 instance C_Tt Ent5 Ent5 where _tt = Tt_5 [] tt_ = Tt_5 instance C_Tt Ent8 Ent5 where _tt = Tt_8 [] tt_ = Tt_8 instance C_Tt Ent9 Ent5 where _tt = Tt_9 [] tt_ = Tt_9 instance C_Tt Ent10 Ent10 where _tt = Tt_10 [] tt_ = Tt_10 instance C_Tt Ent11 Ent10 where _tt = Tt_11 [] tt_ = Tt_11 instance C_Tt Ent12 Ent10 where _tt = Tt_12 [] tt_ = Tt_12 instance C_Tt Ent13 Ent10 where _tt = Tt_13 [] tt_ = Tt_13 instance C_Tt Ent14 Ent10 where _tt = Tt_14 [] tt_ = Tt_14 instance C_Tt Ent15 Ent10 where _tt = Tt_15 [] tt_ = Tt_15 instance C_Tt Ent20 Ent10 where _tt = Tt_20 [] tt_ = Tt_20 instance C_Tt Ent21 Ent10 where _tt = Tt_21 [] tt_ = Tt_21 instance C_Tt Ent23 Ent23 where _tt = Tt_23 [] tt_ = Tt_23 instance C_Tt Ent24 Ent23 where _tt = Tt_24 [] tt_ = Tt_24 instance C_Tt Ent25 Ent23 where _tt = Tt_25 [] tt_ = Tt_25 instance C_Tt Ent26 Ent23 where _tt = Tt_26 [] tt_ = Tt_26 instance C_Tt Ent27 Ent23 where _tt = Tt_27 [] tt_ = Tt_27 instance C_Tt Ent28 Ent23 where _tt = Tt_28 [] tt_ = Tt_28 instance C_Tt Ent29 Ent23 where _tt = Tt_29 [] tt_ = Tt_29 instance C_Tt Ent30 Ent23 where _tt = Tt_30 [] tt_ = Tt_30 instance C_Tt Ent33 Ent23 where _tt = Tt_33 [] tt_ = Tt_33 instance C_Tt Ent34 Ent5 where _tt = Tt_34 [] tt_ = Tt_34 instance C_Tt Ent35 Ent10 where _tt = Tt_35 [] tt_ = Tt_35 instance C_Tt Ent37 Ent23 where _tt = Tt_37 [] tt_ = Tt_37 instance C_Tt Ent38 Ent5 where _tt = Tt_38 [] tt_ = Tt_38 instance C_Tt Ent39 Ent39 where _tt = Tt_39 [] tt_ = Tt_39 instance C_Tt Ent40 Ent39 where _tt = Tt_40 [] tt_ = Tt_40 instance C_Tt Ent41 Ent39 where _tt = Tt_41 [] tt_ = Tt_41 instance C_Tt Ent42 Ent39 where _tt = Tt_42 [] tt_ = Tt_42 instance C_Tt Ent43 Ent39 where _tt = Tt_43 [] tt_ = Tt_43 instance C_Tt Ent44 Ent39 where _tt = Tt_44 [] tt_ = Tt_44 instance C_Tt Ent45 Ent5 where _tt = Tt_45 [] tt_ = Tt_45 instance C_Tt Ent46 Ent39 where _tt = Tt_46 [] tt_ = Tt_46 instance C_Tt Ent47 Ent39 where _tt = Tt_47 [] tt_ = Tt_47 instance C_Tt Ent48 Ent39 where _tt = Tt_48 [] tt_ = Tt_48 instance C_Tt Ent49 Ent5 where _tt = Tt_49 [] tt_ = Tt_49 class C_I a b | a -> b where _i :: [b] -> a i_ :: [Att10] -> [b] -> a instance C_I Ent3 Ent5 where _i = I_3 [] i_ = I_3 instance C_I Ent4 Ent5 where _i = I_4 [] i_ = I_4 instance C_I Ent5 Ent5 where _i = I_5 [] i_ = I_5 instance C_I Ent8 Ent5 where _i = I_8 [] i_ = I_8 instance C_I Ent9 Ent5 where _i = I_9 [] i_ = I_9 instance C_I Ent10 Ent10 where _i = I_10 [] i_ = I_10 instance C_I Ent11 Ent10 where _i = I_11 [] i_ = I_11 instance C_I Ent12 Ent10 where _i = I_12 [] i_ = I_12 instance C_I Ent13 Ent10 where _i = I_13 [] i_ = I_13 instance C_I Ent14 Ent10 where _i = I_14 [] i_ = I_14 instance C_I Ent15 Ent10 where _i = I_15 [] i_ = I_15 instance C_I Ent20 Ent10 where _i = I_20 [] i_ = I_20 instance C_I Ent21 Ent10 where _i = I_21 [] i_ = I_21 instance C_I Ent23 Ent23 where _i = I_23 [] i_ = I_23 instance C_I Ent24 Ent23 where _i = I_24 [] i_ = I_24 instance C_I Ent25 Ent23 where _i = I_25 [] i_ = I_25 instance C_I Ent26 Ent23 where _i = I_26 [] i_ = I_26 instance C_I Ent27 Ent23 where _i = I_27 [] i_ = I_27 instance C_I Ent28 Ent23 where _i = I_28 [] i_ = I_28 instance C_I Ent29 Ent23 where _i = I_29 [] i_ = I_29 instance C_I Ent30 Ent23 where _i = I_30 [] i_ = I_30 instance C_I Ent33 Ent23 where _i = I_33 [] i_ = I_33 instance C_I Ent34 Ent5 where _i = I_34 [] i_ = I_34 instance C_I Ent35 Ent10 where _i = I_35 [] i_ = I_35 instance C_I Ent37 Ent23 where _i = I_37 [] i_ = I_37 instance C_I Ent38 Ent5 where _i = I_38 [] i_ = I_38 instance C_I Ent39 Ent39 where _i = I_39 [] i_ = I_39 instance C_I Ent40 Ent39 where _i = I_40 [] i_ = I_40 instance C_I Ent41 Ent39 where _i = I_41 [] i_ = I_41 instance C_I Ent42 Ent39 where _i = I_42 [] i_ = I_42 instance C_I Ent43 Ent39 where _i = I_43 [] i_ = I_43 instance C_I Ent44 Ent39 where _i = I_44 [] i_ = I_44 instance C_I Ent45 Ent5 where _i = I_45 [] i_ = I_45 instance C_I Ent46 Ent39 where _i = I_46 [] i_ = I_46 instance C_I Ent47 Ent39 where _i = I_47 [] i_ = I_47 instance C_I Ent48 Ent39 where _i = I_48 [] i_ = I_48 instance C_I Ent49 Ent5 where _i = I_49 [] i_ = I_49 class C_B a b | a -> b where _b :: [b] -> a b_ :: [Att10] -> [b] -> a instance C_B Ent3 Ent5 where _b = B_3 [] b_ = B_3 instance C_B Ent4 Ent5 where _b = B_4 [] b_ = B_4 instance C_B Ent5 Ent5 where _b = B_5 [] b_ = B_5 instance C_B Ent8 Ent5 where _b = B_8 [] b_ = B_8 instance C_B Ent9 Ent5 where _b = B_9 [] b_ = B_9 instance C_B Ent10 Ent10 where _b = B_10 [] b_ = B_10 instance C_B Ent11 Ent10 where _b = B_11 [] b_ = B_11 instance C_B Ent12 Ent10 where _b = B_12 [] b_ = B_12 instance C_B Ent13 Ent10 where _b = B_13 [] b_ = B_13 instance C_B Ent14 Ent10 where _b = B_14 [] b_ = B_14 instance C_B Ent15 Ent10 where _b = B_15 [] b_ = B_15 instance C_B Ent20 Ent10 where _b = B_20 [] b_ = B_20 instance C_B Ent21 Ent10 where _b = B_21 [] b_ = B_21 instance C_B Ent23 Ent23 where _b = B_23 [] b_ = B_23 instance C_B Ent24 Ent23 where _b = B_24 [] b_ = B_24 instance C_B Ent25 Ent23 where _b = B_25 [] b_ = B_25 instance C_B Ent26 Ent23 where _b = B_26 [] b_ = B_26 instance C_B Ent27 Ent23 where _b = B_27 [] b_ = B_27 instance C_B Ent28 Ent23 where _b = B_28 [] b_ = B_28 instance C_B Ent29 Ent23 where _b = B_29 [] b_ = B_29 instance C_B Ent30 Ent23 where _b = B_30 [] b_ = B_30 instance C_B Ent33 Ent23 where _b = B_33 [] b_ = B_33 instance C_B Ent34 Ent5 where _b = B_34 [] b_ = B_34 instance C_B Ent35 Ent10 where _b = B_35 [] b_ = B_35 instance C_B Ent37 Ent23 where _b = B_37 [] b_ = B_37 instance C_B Ent38 Ent5 where _b = B_38 [] b_ = B_38 instance C_B Ent39 Ent39 where _b = B_39 [] b_ = B_39 instance C_B Ent40 Ent39 where _b = B_40 [] b_ = B_40 instance C_B Ent41 Ent39 where _b = B_41 [] b_ = B_41 instance C_B Ent42 Ent39 where _b = B_42 [] b_ = B_42 instance C_B Ent43 Ent39 where _b = B_43 [] b_ = B_43 instance C_B Ent44 Ent39 where _b = B_44 [] b_ = B_44 instance C_B Ent45 Ent5 where _b = B_45 [] b_ = B_45 instance C_B Ent46 Ent39 where _b = B_46 [] b_ = B_46 instance C_B Ent47 Ent39 where _b = B_47 [] b_ = B_47 instance C_B Ent48 Ent39 where _b = B_48 [] b_ = B_48 instance C_B Ent49 Ent5 where _b = B_49 [] b_ = B_49 class C_Big a b | a -> b where _big :: [b] -> a big_ :: [Att10] -> [b] -> a instance C_Big Ent3 Ent5 where _big = Big_3 [] big_ = Big_3 instance C_Big Ent4 Ent5 where _big = Big_4 [] big_ = Big_4 instance C_Big Ent5 Ent5 where _big = Big_5 [] big_ = Big_5 instance C_Big Ent8 Ent5 where _big = Big_8 [] big_ = Big_8 instance C_Big Ent10 Ent10 where _big = Big_10 [] big_ = Big_10 instance C_Big Ent11 Ent10 where _big = Big_11 [] big_ = Big_11 instance C_Big Ent12 Ent10 where _big = Big_12 [] big_ = Big_12 instance C_Big Ent14 Ent10 where _big = Big_14 [] big_ = Big_14 instance C_Big Ent15 Ent10 where _big = Big_15 [] big_ = Big_15 instance C_Big Ent20 Ent10 where _big = Big_20 [] big_ = Big_20 instance C_Big Ent21 Ent10 where _big = Big_21 [] big_ = Big_21 instance C_Big Ent23 Ent23 where _big = Big_23 [] big_ = Big_23 instance C_Big Ent24 Ent23 where _big = Big_24 [] big_ = Big_24 instance C_Big Ent25 Ent23 where _big = Big_25 [] big_ = Big_25 instance C_Big Ent27 Ent23 where _big = Big_27 [] big_ = Big_27 instance C_Big Ent28 Ent23 where _big = Big_28 [] big_ = Big_28 instance C_Big Ent29 Ent23 where _big = Big_29 [] big_ = Big_29 instance C_Big Ent30 Ent23 where _big = Big_30 [] big_ = Big_30 instance C_Big Ent33 Ent23 where _big = Big_33 [] big_ = Big_33 instance C_Big Ent34 Ent5 where _big = Big_34 [] big_ = Big_34 instance C_Big Ent35 Ent10 where _big = Big_35 [] big_ = Big_35 instance C_Big Ent37 Ent23 where _big = Big_37 [] big_ = Big_37 instance C_Big Ent38 Ent5 where _big = Big_38 [] big_ = Big_38 instance C_Big Ent39 Ent39 where _big = Big_39 [] big_ = Big_39 instance C_Big Ent40 Ent39 where _big = Big_40 [] big_ = Big_40 instance C_Big Ent41 Ent39 where _big = Big_41 [] big_ = Big_41 instance C_Big Ent43 Ent39 where _big = Big_43 [] big_ = Big_43 instance C_Big Ent44 Ent39 where _big = Big_44 [] big_ = Big_44 instance C_Big Ent45 Ent5 where _big = Big_45 [] big_ = Big_45 instance C_Big Ent46 Ent39 where _big = Big_46 [] big_ = Big_46 instance C_Big Ent47 Ent39 where _big = Big_47 [] big_ = Big_47 instance C_Big Ent48 Ent39 where _big = Big_48 [] big_ = Big_48 instance C_Big Ent49 Ent5 where _big = Big_49 [] big_ = Big_49 class C_Small a b | a -> b where _small :: [b] -> a small_ :: [Att10] -> [b] -> a instance C_Small Ent3 Ent5 where _small = Small_3 [] small_ = Small_3 instance C_Small Ent4 Ent5 where _small = Small_4 [] small_ = Small_4 instance C_Small Ent5 Ent5 where _small = Small_5 [] small_ = Small_5 instance C_Small Ent8 Ent5 where _small = Small_8 [] small_ = Small_8 instance C_Small Ent10 Ent10 where _small = Small_10 [] small_ = Small_10 instance C_Small Ent11 Ent10 where _small = Small_11 [] small_ = Small_11 instance C_Small Ent12 Ent10 where _small = Small_12 [] small_ = Small_12 instance C_Small Ent14 Ent10 where _small = Small_14 [] small_ = Small_14 instance C_Small Ent15 Ent10 where _small = Small_15 [] small_ = Small_15 instance C_Small Ent20 Ent10 where _small = Small_20 [] small_ = Small_20 instance C_Small Ent21 Ent10 where _small = Small_21 [] small_ = Small_21 instance C_Small Ent23 Ent23 where _small = Small_23 [] small_ = Small_23 instance C_Small Ent24 Ent23 where _small = Small_24 [] small_ = Small_24 instance C_Small Ent25 Ent23 where _small = Small_25 [] small_ = Small_25 instance C_Small Ent27 Ent23 where _small = Small_27 [] small_ = Small_27 instance C_Small Ent28 Ent23 where _small = Small_28 [] small_ = Small_28 instance C_Small Ent29 Ent23 where _small = Small_29 [] small_ = Small_29 instance C_Small Ent30 Ent23 where _small = Small_30 [] small_ = Small_30 instance C_Small Ent33 Ent23 where _small = Small_33 [] small_ = Small_33 instance C_Small Ent34 Ent5 where _small = Small_34 [] small_ = Small_34 instance C_Small Ent35 Ent10 where _small = Small_35 [] small_ = Small_35 instance C_Small Ent37 Ent23 where _small = Small_37 [] small_ = Small_37 instance C_Small Ent38 Ent5 where _small = Small_38 [] small_ = Small_38 instance C_Small Ent39 Ent39 where _small = Small_39 [] small_ = Small_39 instance C_Small Ent40 Ent39 where _small = Small_40 [] small_ = Small_40 instance C_Small Ent41 Ent39 where _small = Small_41 [] small_ = Small_41 instance C_Small Ent43 Ent39 where _small = Small_43 [] small_ = Small_43 instance C_Small Ent44 Ent39 where _small = Small_44 [] small_ = Small_44 instance C_Small Ent45 Ent5 where _small = Small_45 [] small_ = Small_45 instance C_Small Ent46 Ent39 where _small = Small_46 [] small_ = Small_46 instance C_Small Ent47 Ent39 where _small = Small_47 [] small_ = Small_47 instance C_Small Ent48 Ent39 where _small = Small_48 [] small_ = Small_48 instance C_Small Ent49 Ent5 where _small = Small_49 [] small_ = Small_49 class C_U a b | a -> b where _u :: [b] -> a u_ :: [Att10] -> [b] -> a instance C_U Ent3 Ent5 where _u = U_3 [] u_ = U_3 instance C_U Ent4 Ent5 where _u = U_4 [] u_ = U_4 instance C_U Ent5 Ent5 where _u = U_5 [] u_ = U_5 instance C_U Ent8 Ent5 where _u = U_8 [] u_ = U_8 instance C_U Ent9 Ent5 where _u = U_9 [] u_ = U_9 instance C_U Ent10 Ent10 where _u = U_10 [] u_ = U_10 instance C_U Ent11 Ent10 where _u = U_11 [] u_ = U_11 instance C_U Ent12 Ent10 where _u = U_12 [] u_ = U_12 instance C_U Ent13 Ent10 where _u = U_13 [] u_ = U_13 instance C_U Ent14 Ent10 where _u = U_14 [] u_ = U_14 instance C_U Ent15 Ent10 where _u = U_15 [] u_ = U_15 instance C_U Ent20 Ent10 where _u = U_20 [] u_ = U_20 instance C_U Ent21 Ent10 where _u = U_21 [] u_ = U_21 instance C_U Ent23 Ent23 where _u = U_23 [] u_ = U_23 instance C_U Ent24 Ent23 where _u = U_24 [] u_ = U_24 instance C_U Ent25 Ent23 where _u = U_25 [] u_ = U_25 instance C_U Ent26 Ent23 where _u = U_26 [] u_ = U_26 instance C_U Ent27 Ent23 where _u = U_27 [] u_ = U_27 instance C_U Ent28 Ent23 where _u = U_28 [] u_ = U_28 instance C_U Ent29 Ent23 where _u = U_29 [] u_ = U_29 instance C_U Ent30 Ent23 where _u = U_30 [] u_ = U_30 instance C_U Ent33 Ent23 where _u = U_33 [] u_ = U_33 instance C_U Ent34 Ent5 where _u = U_34 [] u_ = U_34 instance C_U Ent35 Ent10 where _u = U_35 [] u_ = U_35 instance C_U Ent37 Ent23 where _u = U_37 [] u_ = U_37 instance C_U Ent38 Ent5 where _u = U_38 [] u_ = U_38 instance C_U Ent39 Ent39 where _u = U_39 [] u_ = U_39 instance C_U Ent40 Ent39 where _u = U_40 [] u_ = U_40 instance C_U Ent41 Ent39 where _u = U_41 [] u_ = U_41 instance C_U Ent42 Ent39 where _u = U_42 [] u_ = U_42 instance C_U Ent43 Ent39 where _u = U_43 [] u_ = U_43 instance C_U Ent44 Ent39 where _u = U_44 [] u_ = U_44 instance C_U Ent45 Ent5 where _u = U_45 [] u_ = U_45 instance C_U Ent46 Ent39 where _u = U_46 [] u_ = U_46 instance C_U Ent47 Ent39 where _u = U_47 [] u_ = U_47 instance C_U Ent48 Ent39 where _u = U_48 [] u_ = U_48 instance C_U Ent49 Ent5 where _u = U_49 [] u_ = U_49 class C_S a b | a -> b where _s :: [b] -> a s_ :: [Att10] -> [b] -> a instance C_S Ent3 Ent5 where _s = S_3 [] s_ = S_3 instance C_S Ent4 Ent5 where _s = S_4 [] s_ = S_4 instance C_S Ent5 Ent5 where _s = S_5 [] s_ = S_5 instance C_S Ent8 Ent5 where _s = S_8 [] s_ = S_8 instance C_S Ent9 Ent5 where _s = S_9 [] s_ = S_9 instance C_S Ent10 Ent10 where _s = S_10 [] s_ = S_10 instance C_S Ent11 Ent10 where _s = S_11 [] s_ = S_11 instance C_S Ent12 Ent10 where _s = S_12 [] s_ = S_12 instance C_S Ent13 Ent10 where _s = S_13 [] s_ = S_13 instance C_S Ent14 Ent10 where _s = S_14 [] s_ = S_14 instance C_S Ent15 Ent10 where _s = S_15 [] s_ = S_15 instance C_S Ent20 Ent10 where _s = S_20 [] s_ = S_20 instance C_S Ent21 Ent10 where _s = S_21 [] s_ = S_21 instance C_S Ent23 Ent23 where _s = S_23 [] s_ = S_23 instance C_S Ent24 Ent23 where _s = S_24 [] s_ = S_24 instance C_S Ent25 Ent23 where _s = S_25 [] s_ = S_25 instance C_S Ent26 Ent23 where _s = S_26 [] s_ = S_26 instance C_S Ent27 Ent23 where _s = S_27 [] s_ = S_27 instance C_S Ent28 Ent23 where _s = S_28 [] s_ = S_28 instance C_S Ent29 Ent23 where _s = S_29 [] s_ = S_29 instance C_S Ent30 Ent23 where _s = S_30 [] s_ = S_30 instance C_S Ent33 Ent23 where _s = S_33 [] s_ = S_33 instance C_S Ent34 Ent5 where _s = S_34 [] s_ = S_34 instance C_S Ent35 Ent10 where _s = S_35 [] s_ = S_35 instance C_S Ent37 Ent23 where _s = S_37 [] s_ = S_37 instance C_S Ent38 Ent5 where _s = S_38 [] s_ = S_38 instance C_S Ent39 Ent39 where _s = S_39 [] s_ = S_39 instance C_S Ent40 Ent39 where _s = S_40 [] s_ = S_40 instance C_S Ent41 Ent39 where _s = S_41 [] s_ = S_41 instance C_S Ent42 Ent39 where _s = S_42 [] s_ = S_42 instance C_S Ent43 Ent39 where _s = S_43 [] s_ = S_43 instance C_S Ent44 Ent39 where _s = S_44 [] s_ = S_44 instance C_S Ent45 Ent5 where _s = S_45 [] s_ = S_45 instance C_S Ent46 Ent39 where _s = S_46 [] s_ = S_46 instance C_S Ent47 Ent39 where _s = S_47 [] s_ = S_47 instance C_S Ent48 Ent39 where _s = S_48 [] s_ = S_48 instance C_S Ent49 Ent5 where _s = S_49 [] s_ = S_49 class C_Strike a b | a -> b where _strike :: [b] -> a strike_ :: [Att10] -> [b] -> a instance C_Strike Ent3 Ent5 where _strike = Strike_3 [] strike_ = Strike_3 instance C_Strike Ent4 Ent5 where _strike = Strike_4 [] strike_ = Strike_4 instance C_Strike Ent5 Ent5 where _strike = Strike_5 [] strike_ = Strike_5 instance C_Strike Ent8 Ent5 where _strike = Strike_8 [] strike_ = Strike_8 instance C_Strike Ent9 Ent5 where _strike = Strike_9 [] strike_ = Strike_9 instance C_Strike Ent10 Ent10 where _strike = Strike_10 [] strike_ = Strike_10 instance C_Strike Ent11 Ent10 where _strike = Strike_11 [] strike_ = Strike_11 instance C_Strike Ent12 Ent10 where _strike = Strike_12 [] strike_ = Strike_12 instance C_Strike Ent13 Ent10 where _strike = Strike_13 [] strike_ = Strike_13 instance C_Strike Ent14 Ent10 where _strike = Strike_14 [] strike_ = Strike_14 instance C_Strike Ent15 Ent10 where _strike = Strike_15 [] strike_ = Strike_15 instance C_Strike Ent20 Ent10 where _strike = Strike_20 [] strike_ = Strike_20 instance C_Strike Ent21 Ent10 where _strike = Strike_21 [] strike_ = Strike_21 instance C_Strike Ent23 Ent23 where _strike = Strike_23 [] strike_ = Strike_23 instance C_Strike Ent24 Ent23 where _strike = Strike_24 [] strike_ = Strike_24 instance C_Strike Ent25 Ent23 where _strike = Strike_25 [] strike_ = Strike_25 instance C_Strike Ent26 Ent23 where _strike = Strike_26 [] strike_ = Strike_26 instance C_Strike Ent27 Ent23 where _strike = Strike_27 [] strike_ = Strike_27 instance C_Strike Ent28 Ent23 where _strike = Strike_28 [] strike_ = Strike_28 instance C_Strike Ent29 Ent23 where _strike = Strike_29 [] strike_ = Strike_29 instance C_Strike Ent30 Ent23 where _strike = Strike_30 [] strike_ = Strike_30 instance C_Strike Ent33 Ent23 where _strike = Strike_33 [] strike_ = Strike_33 instance C_Strike Ent34 Ent5 where _strike = Strike_34 [] strike_ = Strike_34 instance C_Strike Ent35 Ent10 where _strike = Strike_35 [] strike_ = Strike_35 instance C_Strike Ent37 Ent23 where _strike = Strike_37 [] strike_ = Strike_37 instance C_Strike Ent38 Ent5 where _strike = Strike_38 [] strike_ = Strike_38 instance C_Strike Ent39 Ent39 where _strike = Strike_39 [] strike_ = Strike_39 instance C_Strike Ent40 Ent39 where _strike = Strike_40 [] strike_ = Strike_40 instance C_Strike Ent41 Ent39 where _strike = Strike_41 [] strike_ = Strike_41 instance C_Strike Ent42 Ent39 where _strike = Strike_42 [] strike_ = Strike_42 instance C_Strike Ent43 Ent39 where _strike = Strike_43 [] strike_ = Strike_43 instance C_Strike Ent44 Ent39 where _strike = Strike_44 [] strike_ = Strike_44 instance C_Strike Ent45 Ent5 where _strike = Strike_45 [] strike_ = Strike_45 instance C_Strike Ent46 Ent39 where _strike = Strike_46 [] strike_ = Strike_46 instance C_Strike Ent47 Ent39 where _strike = Strike_47 [] strike_ = Strike_47 instance C_Strike Ent48 Ent39 where _strike = Strike_48 [] strike_ = Strike_48 instance C_Strike Ent49 Ent5 where _strike = Strike_49 [] strike_ = Strike_49 class C_Basefont a where _basefont :: a basefont_ :: [Att28] -> a instance C_Basefont Ent3 where _basefont = Basefont_3 [] basefont_ = Basefont_3 instance C_Basefont Ent4 where _basefont = Basefont_4 [] basefont_ = Basefont_4 instance C_Basefont Ent5 where _basefont = Basefont_5 [] basefont_ = Basefont_5 instance C_Basefont Ent8 where _basefont = Basefont_8 [] basefont_ = Basefont_8 instance C_Basefont Ent10 where _basefont = Basefont_10 [] basefont_ = Basefont_10 instance C_Basefont Ent11 where _basefont = Basefont_11 [] basefont_ = Basefont_11 instance C_Basefont Ent12 where _basefont = Basefont_12 [] basefont_ = Basefont_12 instance C_Basefont Ent14 where _basefont = Basefont_14 [] basefont_ = Basefont_14 instance C_Basefont Ent15 where _basefont = Basefont_15 [] basefont_ = Basefont_15 instance C_Basefont Ent20 where _basefont = Basefont_20 [] basefont_ = Basefont_20 instance C_Basefont Ent21 where _basefont = Basefont_21 [] basefont_ = Basefont_21 instance C_Basefont Ent23 where _basefont = Basefont_23 [] basefont_ = Basefont_23 instance C_Basefont Ent24 where _basefont = Basefont_24 [] basefont_ = Basefont_24 instance C_Basefont Ent25 where _basefont = Basefont_25 [] basefont_ = Basefont_25 instance C_Basefont Ent27 where _basefont = Basefont_27 [] basefont_ = Basefont_27 instance C_Basefont Ent28 where _basefont = Basefont_28 [] basefont_ = Basefont_28 instance C_Basefont Ent29 where _basefont = Basefont_29 [] basefont_ = Basefont_29 instance C_Basefont Ent30 where _basefont = Basefont_30 [] basefont_ = Basefont_30 instance C_Basefont Ent33 where _basefont = Basefont_33 [] basefont_ = Basefont_33 instance C_Basefont Ent34 where _basefont = Basefont_34 [] basefont_ = Basefont_34 instance C_Basefont Ent35 where _basefont = Basefont_35 [] basefont_ = Basefont_35 instance C_Basefont Ent37 where _basefont = Basefont_37 [] basefont_ = Basefont_37 instance C_Basefont Ent38 where _basefont = Basefont_38 [] basefont_ = Basefont_38 instance C_Basefont Ent39 where _basefont = Basefont_39 [] basefont_ = Basefont_39 instance C_Basefont Ent40 where _basefont = Basefont_40 [] basefont_ = Basefont_40 instance C_Basefont Ent41 where _basefont = Basefont_41 [] basefont_ = Basefont_41 instance C_Basefont Ent43 where _basefont = Basefont_43 [] basefont_ = Basefont_43 instance C_Basefont Ent44 where _basefont = Basefont_44 [] basefont_ = Basefont_44 instance C_Basefont Ent45 where _basefont = Basefont_45 [] basefont_ = Basefont_45 instance C_Basefont Ent46 where _basefont = Basefont_46 [] basefont_ = Basefont_46 instance C_Basefont Ent47 where _basefont = Basefont_47 [] basefont_ = Basefont_47 instance C_Basefont Ent48 where _basefont = Basefont_48 [] basefont_ = Basefont_48 instance C_Basefont Ent49 where _basefont = Basefont_49 [] basefont_ = Basefont_49 class C_Font a b | a -> b where _font :: [b] -> a font_ :: [Att30] -> [b] -> a instance C_Font Ent3 Ent5 where _font = Font_3 [] font_ = Font_3 instance C_Font Ent4 Ent5 where _font = Font_4 [] font_ = Font_4 instance C_Font Ent5 Ent5 where _font = Font_5 [] font_ = Font_5 instance C_Font Ent8 Ent5 where _font = Font_8 [] font_ = Font_8 instance C_Font Ent10 Ent10 where _font = Font_10 [] font_ = Font_10 instance C_Font Ent11 Ent10 where _font = Font_11 [] font_ = Font_11 instance C_Font Ent12 Ent10 where _font = Font_12 [] font_ = Font_12 instance C_Font Ent14 Ent10 where _font = Font_14 [] font_ = Font_14 instance C_Font Ent15 Ent10 where _font = Font_15 [] font_ = Font_15 instance C_Font Ent20 Ent10 where _font = Font_20 [] font_ = Font_20 instance C_Font Ent21 Ent10 where _font = Font_21 [] font_ = Font_21 instance C_Font Ent23 Ent23 where _font = Font_23 [] font_ = Font_23 instance C_Font Ent24 Ent23 where _font = Font_24 [] font_ = Font_24 instance C_Font Ent25 Ent23 where _font = Font_25 [] font_ = Font_25 instance C_Font Ent27 Ent23 where _font = Font_27 [] font_ = Font_27 instance C_Font Ent28 Ent23 where _font = Font_28 [] font_ = Font_28 instance C_Font Ent29 Ent23 where _font = Font_29 [] font_ = Font_29 instance C_Font Ent30 Ent23 where _font = Font_30 [] font_ = Font_30 instance C_Font Ent33 Ent23 where _font = Font_33 [] font_ = Font_33 instance C_Font Ent34 Ent5 where _font = Font_34 [] font_ = Font_34 instance C_Font Ent35 Ent10 where _font = Font_35 [] font_ = Font_35 instance C_Font Ent37 Ent23 where _font = Font_37 [] font_ = Font_37 instance C_Font Ent38 Ent5 where _font = Font_38 [] font_ = Font_38 instance C_Font Ent39 Ent39 where _font = Font_39 [] font_ = Font_39 instance C_Font Ent40 Ent39 where _font = Font_40 [] font_ = Font_40 instance C_Font Ent41 Ent39 where _font = Font_41 [] font_ = Font_41 instance C_Font Ent43 Ent39 where _font = Font_43 [] font_ = Font_43 instance C_Font Ent44 Ent39 where _font = Font_44 [] font_ = Font_44 instance C_Font Ent45 Ent5 where _font = Font_45 [] font_ = Font_45 instance C_Font Ent46 Ent39 where _font = Font_46 [] font_ = Font_46 instance C_Font Ent47 Ent39 where _font = Font_47 [] font_ = Font_47 instance C_Font Ent48 Ent39 where _font = Font_48 [] font_ = Font_48 instance C_Font Ent49 Ent5 where _font = Font_49 [] font_ = Font_49 class C_Object a b | a -> b where _object :: [b] -> a object_ :: [Att31] -> [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 Ent3 where _object = Object_4 [] object_ = Object_4 instance C_Object Ent5 Ent3 where _object = Object_5 [] object_ = Object_5 instance C_Object Ent8 Ent3 where _object = Object_8 [] object_ = Object_8 instance C_Object Ent10 Ent21 where _object = Object_10 [] object_ = Object_10 instance C_Object Ent11 Ent21 where _object = Object_11 [] object_ = Object_11 instance C_Object Ent12 Ent21 where _object = Object_12 [] object_ = Object_12 instance C_Object Ent14 Ent35 where _object = Object_14 [] object_ = Object_14 instance C_Object Ent15 Ent35 where _object = Object_15 [] object_ = Object_15 instance C_Object Ent20 Ent21 where _object = Object_20 [] object_ = Object_20 instance C_Object Ent21 Ent21 where _object = Object_21 [] object_ = Object_21 instance C_Object Ent23 Ent30 where _object = Object_23 [] object_ = Object_23 instance C_Object Ent24 Ent30 where _object = Object_24 [] object_ = Object_24 instance C_Object Ent25 Ent30 where _object = Object_25 [] object_ = Object_25 instance C_Object Ent27 Ent37 where _object = Object_27 [] object_ = Object_27 instance C_Object Ent28 Ent37 where _object = Object_28 [] object_ = Object_28 instance C_Object Ent29 Ent30 where _object = Object_29 [] object_ = Object_29 instance C_Object Ent30 Ent30 where _object = Object_30 [] object_ = Object_30 instance C_Object Ent33 Ent30 where _object = Object_33 [] object_ = Object_33 instance C_Object Ent34 Ent38 where _object = Object_34 [] object_ = Object_34 instance C_Object Ent35 Ent35 where _object = Object_35 [] object_ = Object_35 instance C_Object Ent37 Ent37 where _object = Object_37 [] object_ = Object_37 instance C_Object Ent38 Ent38 where _object = Object_38 [] object_ = Object_38 instance C_Object Ent39 Ent44 where _object = Object_39 [] object_ = Object_39 instance C_Object Ent40 Ent44 where _object = Object_40 [] object_ = Object_40 instance C_Object Ent41 Ent44 where _object = Object_41 [] object_ = Object_41 instance C_Object Ent43 Ent44 where _object = Object_43 [] object_ = Object_43 instance C_Object Ent44 Ent44 where _object = Object_44 [] object_ = Object_44 instance C_Object Ent45 Ent38 where _object = Object_45 [] object_ = Object_45 instance C_Object Ent46 Ent48 where _object = Object_46 [] object_ = Object_46 instance C_Object Ent47 Ent48 where _object = Object_47 [] object_ = Object_47 instance C_Object Ent48 Ent48 where _object = Object_48 [] object_ = Object_48 instance C_Object Ent49 Ent3 where _object = Object_49 [] object_ = Object_49 class C_Param a where _param :: a param_ :: [Att32] -> a instance C_Param Ent3 where _param = Param_3 [] param_ = Param_3 instance C_Param Ent21 where _param = Param_21 [] param_ = Param_21 instance C_Param Ent30 where _param = Param_30 [] param_ = Param_30 instance C_Param Ent35 where _param = Param_35 [] param_ = Param_35 instance C_Param Ent37 where _param = Param_37 [] param_ = Param_37 instance C_Param Ent38 where _param = Param_38 [] param_ = Param_38 instance C_Param Ent44 where _param = Param_44 [] param_ = Param_44 instance C_Param Ent48 where _param = Param_48 [] param_ = Param_48 class C_Applet a b | a -> b where _applet :: [b] -> a applet_ :: [Att34] -> [b] -> a instance C_Applet Ent3 Ent3 where _applet = Applet_3 [] applet_ = Applet_3 instance C_Applet Ent4 Ent3 where _applet = Applet_4 [] applet_ = Applet_4 instance C_Applet Ent5 Ent3 where _applet = Applet_5 [] applet_ = Applet_5 instance C_Applet Ent8 Ent3 where _applet = Applet_8 [] applet_ = Applet_8 instance C_Applet Ent10 Ent21 where _applet = Applet_10 [] applet_ = Applet_10 instance C_Applet Ent11 Ent21 where _applet = Applet_11 [] applet_ = Applet_11 instance C_Applet Ent12 Ent21 where _applet = Applet_12 [] applet_ = Applet_12 instance C_Applet Ent14 Ent35 where _applet = Applet_14 [] applet_ = Applet_14 instance C_Applet Ent15 Ent35 where _applet = Applet_15 [] applet_ = Applet_15 instance C_Applet Ent20 Ent21 where _applet = Applet_20 [] applet_ = Applet_20 instance C_Applet Ent21 Ent21 where _applet = Applet_21 [] applet_ = Applet_21 instance C_Applet Ent23 Ent30 where _applet = Applet_23 [] applet_ = Applet_23 instance C_Applet Ent24 Ent30 where _applet = Applet_24 [] applet_ = Applet_24 instance C_Applet Ent25 Ent30 where _applet = Applet_25 [] applet_ = Applet_25 instance C_Applet Ent27 Ent37 where _applet = Applet_27 [] applet_ = Applet_27 instance C_Applet Ent28 Ent37 where _applet = Applet_28 [] applet_ = Applet_28 instance C_Applet Ent29 Ent30 where _applet = Applet_29 [] applet_ = Applet_29 instance C_Applet Ent30 Ent30 where _applet = Applet_30 [] applet_ = Applet_30 instance C_Applet Ent33 Ent30 where _applet = Applet_33 [] applet_ = Applet_33 instance C_Applet Ent34 Ent38 where _applet = Applet_34 [] applet_ = Applet_34 instance C_Applet Ent35 Ent35 where _applet = Applet_35 [] applet_ = Applet_35 instance C_Applet Ent37 Ent37 where _applet = Applet_37 [] applet_ = Applet_37 instance C_Applet Ent38 Ent38 where _applet = Applet_38 [] applet_ = Applet_38 instance C_Applet Ent39 Ent44 where _applet = Applet_39 [] applet_ = Applet_39 instance C_Applet Ent40 Ent44 where _applet = Applet_40 [] applet_ = Applet_40 instance C_Applet Ent41 Ent44 where _applet = Applet_41 [] applet_ = Applet_41 instance C_Applet Ent43 Ent44 where _applet = Applet_43 [] applet_ = Applet_43 instance C_Applet Ent44 Ent44 where _applet = Applet_44 [] applet_ = Applet_44 instance C_Applet Ent45 Ent38 where _applet = Applet_45 [] applet_ = Applet_45 instance C_Applet Ent46 Ent48 where _applet = Applet_46 [] applet_ = Applet_46 instance C_Applet Ent47 Ent48 where _applet = Applet_47 [] applet_ = Applet_47 instance C_Applet Ent48 Ent48 where _applet = Applet_48 [] applet_ = Applet_48 instance C_Applet Ent49 Ent3 where _applet = Applet_49 [] applet_ = Applet_49 class C_Img a where _img :: a img_ :: [Att37] -> 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 Ent8 where _img = Img_8 [] img_ = Img_8 instance C_Img Ent10 where _img = Img_10 [] img_ = Img_10 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 Ent14 where _img = Img_14 [] img_ = Img_14 instance C_Img Ent15 where _img = Img_15 [] img_ = Img_15 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 Ent27 where _img = Img_27 [] img_ = Img_27 instance C_Img Ent28 where _img = Img_28 [] img_ = Img_28 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 Ent33 where _img = Img_33 [] img_ = Img_33 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 Ent37 where _img = Img_37 [] img_ = Img_37 instance C_Img Ent38 where _img = Img_38 [] img_ = Img_38 instance C_Img Ent39 where _img = Img_39 [] img_ = Img_39 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 instance C_Img Ent48 where _img = Img_48 [] img_ = Img_48 instance C_Img Ent49 where _img = Img_49 [] img_ = Img_49 class C_Map a b | a -> b where _map :: [b] -> a map_ :: [Att40] -> [b] -> a instance C_Map Ent3 Ent22 where _map = Map_3 [] map_ = Map_3 instance C_Map Ent4 Ent22 where _map = Map_4 [] map_ = Map_4 instance C_Map Ent5 Ent22 where _map = Map_5 [] map_ = Map_5 instance C_Map Ent8 Ent22 where _map = Map_8 [] map_ = Map_8 instance C_Map Ent10 Ent22 where _map = Map_10 [] map_ = Map_10 instance C_Map Ent11 Ent22 where _map = Map_11 [] map_ = Map_11 instance C_Map Ent12 Ent22 where _map = Map_12 [] map_ = Map_12 instance C_Map Ent14 Ent36 where _map = Map_14 [] map_ = Map_14 instance C_Map Ent15 Ent36 where _map = Map_15 [] map_ = Map_15 instance C_Map Ent20 Ent22 where _map = Map_20 [] map_ = Map_20 instance C_Map Ent21 Ent22 where _map = Map_21 [] map_ = Map_21 instance C_Map Ent23 Ent22 where _map = Map_23 [] map_ = Map_23 instance C_Map Ent24 Ent22 where _map = Map_24 [] map_ = Map_24 instance C_Map Ent25 Ent22 where _map = Map_25 [] map_ = Map_25 instance C_Map Ent27 Ent36 where _map = Map_27 [] map_ = Map_27 instance C_Map Ent28 Ent36 where _map = Map_28 [] map_ = Map_28 instance C_Map Ent29 Ent22 where _map = Map_29 [] map_ = Map_29 instance C_Map Ent30 Ent22 where _map = Map_30 [] map_ = Map_30 instance C_Map Ent33 Ent22 where _map = Map_33 [] map_ = Map_33 instance C_Map Ent34 Ent36 where _map = Map_34 [] map_ = Map_34 instance C_Map Ent35 Ent36 where _map = Map_35 [] map_ = Map_35 instance C_Map Ent37 Ent36 where _map = Map_37 [] map_ = Map_37 instance C_Map Ent38 Ent36 where _map = Map_38 [] map_ = Map_38 instance C_Map Ent39 Ent36 where _map = Map_39 [] map_ = Map_39 instance C_Map Ent40 Ent36 where _map = Map_40 [] map_ = Map_40 instance C_Map Ent41 Ent36 where _map = Map_41 [] map_ = Map_41 instance C_Map Ent43 Ent36 where _map = Map_43 [] map_ = Map_43 instance C_Map Ent44 Ent36 where _map = Map_44 [] map_ = Map_44 instance C_Map Ent45 Ent36 where _map = Map_45 [] map_ = Map_45 instance C_Map Ent46 Ent22 where _map = Map_46 [] map_ = Map_46 instance C_Map Ent47 Ent22 where _map = Map_47 [] map_ = Map_47 instance C_Map Ent48 Ent22 where _map = Map_48 [] map_ = Map_48 instance C_Map Ent49 Ent22 where _map = Map_49 [] map_ = Map_49 class C_Area a where _area :: a area_ :: [Att42] -> a instance C_Area Ent22 where _area = Area_22 [] area_ = Area_22 instance C_Area Ent36 where _area = Area_36 [] area_ = Area_36 class C_Form a b | a -> b where _form :: [b] -> a form_ :: [Att43] -> [b] -> a instance C_Form Ent3 Ent34 where _form = Form_3 [] form_ = Form_3 instance C_Form Ent4 Ent34 where _form = Form_4 [] form_ = Form_4 instance C_Form Ent11 Ent14 where _form = Form_11 [] form_ = Form_11 instance C_Form Ent20 Ent14 where _form = Form_20 [] form_ = Form_20 instance C_Form Ent21 Ent14 where _form = Form_21 [] form_ = Form_21 instance C_Form Ent22 Ent14 where _form = Form_22 [] form_ = Form_22 instance C_Form Ent24 Ent27 where _form = Form_24 [] form_ = Form_24 instance C_Form Ent29 Ent27 where _form = Form_29 [] form_ = Form_29 instance C_Form Ent30 Ent27 where _form = Form_30 [] form_ = Form_30 instance C_Form Ent46 Ent40 where _form = Form_46 [] form_ = Form_46 instance C_Form Ent47 Ent40 where _form = Form_47 [] form_ = Form_47 instance C_Form Ent48 Ent40 where _form = Form_48 [] form_ = Form_48 instance C_Form Ent49 Ent34 where _form = Form_49 [] form_ = Form_49 class C_Label a b | a -> b where _label :: [b] -> a label_ :: [Att45] -> [b] -> a instance C_Label Ent3 Ent39 where _label = Label_3 [] label_ = Label_3 instance C_Label Ent4 Ent39 where _label = Label_4 [] label_ = Label_4 instance C_Label Ent5 Ent39 where _label = Label_5 [] label_ = Label_5 instance C_Label Ent8 Ent39 where _label = Label_8 [] label_ = Label_8 instance C_Label Ent9 Ent39 where _label = Label_9 [] label_ = Label_9 instance C_Label Ent10 Ent23 where _label = Label_10 [] label_ = Label_10 instance C_Label Ent11 Ent23 where _label = Label_11 [] label_ = Label_11 instance C_Label Ent12 Ent23 where _label = Label_12 [] label_ = Label_12 instance C_Label Ent13 Ent23 where _label = Label_13 [] label_ = Label_13 instance C_Label Ent14 Ent23 where _label = Label_14 [] label_ = Label_14 instance C_Label Ent15 Ent23 where _label = Label_15 [] label_ = Label_15 instance C_Label Ent20 Ent23 where _label = Label_20 [] label_ = Label_20 instance C_Label Ent21 Ent23 where _label = Label_21 [] label_ = Label_21 instance C_Label Ent34 Ent39 where _label = Label_34 [] label_ = Label_34 instance C_Label Ent35 Ent23 where _label = Label_35 [] label_ = Label_35 instance C_Label Ent38 Ent39 where _label = Label_38 [] label_ = Label_38 instance C_Label Ent45 Ent39 where _label = Label_45 [] label_ = Label_45 instance C_Label Ent49 Ent39 where _label = Label_49 [] label_ = Label_49 class C_Input a where _input :: a input_ :: [Att46] -> 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 Ent8 where _input = Input_8 [] input_ = Input_8 instance C_Input Ent9 where _input = Input_9 [] input_ = Input_9 instance C_Input Ent10 where _input = Input_10 [] input_ = Input_10 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 Ent13 where _input = Input_13 [] input_ = Input_13 instance C_Input Ent14 where _input = Input_14 [] input_ = Input_14 instance C_Input Ent15 where _input = Input_15 [] input_ = Input_15 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 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 Ent27 where _input = Input_27 [] input_ = Input_27 instance C_Input Ent28 where _input = Input_28 [] input_ = Input_28 instance C_Input Ent29 where _input = Input_29 [] input_ = Input_29 instance C_Input Ent30 where _input = Input_30 [] input_ = Input_30 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 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 Ent42 where _input = Input_42 [] input_ = Input_42 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 instance C_Input Ent48 where _input = Input_48 [] input_ = Input_48 instance C_Input Ent49 where _input = Input_49 [] input_ = Input_49 class C_Select a b | a -> b where _select :: [b] -> a select_ :: [Att47] -> [b] -> a instance C_Select Ent3 Ent31 where _select = Select_3 [] select_ = Select_3 instance C_Select Ent4 Ent31 where _select = Select_4 [] select_ = Select_4 instance C_Select Ent5 Ent31 where _select = Select_5 [] select_ = Select_5 instance C_Select Ent8 Ent31 where _select = Select_8 [] select_ = Select_8 instance C_Select Ent9 Ent31 where _select = Select_9 [] select_ = Select_9 instance C_Select Ent10 Ent31 where _select = Select_10 [] select_ = Select_10 instance C_Select Ent11 Ent31 where _select = Select_11 [] select_ = Select_11 instance C_Select Ent12 Ent31 where _select = Select_12 [] select_ = Select_12 instance C_Select Ent13 Ent31 where _select = Select_13 [] select_ = Select_13 instance C_Select Ent14 Ent31 where _select = Select_14 [] select_ = Select_14 instance C_Select Ent15 Ent31 where _select = Select_15 [] select_ = Select_15 instance C_Select Ent20 Ent31 where _select = Select_20 [] select_ = Select_20 instance C_Select Ent21 Ent31 where _select = Select_21 [] select_ = Select_21 instance C_Select Ent23 Ent31 where _select = Select_23 [] select_ = Select_23 instance C_Select Ent24 Ent31 where _select = Select_24 [] select_ = Select_24 instance C_Select Ent25 Ent31 where _select = Select_25 [] select_ = Select_25 instance C_Select Ent26 Ent31 where _select = Select_26 [] select_ = Select_26 instance C_Select Ent27 Ent31 where _select = Select_27 [] select_ = Select_27 instance C_Select Ent28 Ent31 where _select = Select_28 [] select_ = Select_28 instance C_Select Ent29 Ent31 where _select = Select_29 [] select_ = Select_29 instance C_Select Ent30 Ent31 where _select = Select_30 [] select_ = Select_30 instance C_Select Ent34 Ent31 where _select = Select_34 [] select_ = Select_34 instance C_Select Ent35 Ent31 where _select = Select_35 [] select_ = Select_35 instance C_Select Ent37 Ent31 where _select = Select_37 [] select_ = Select_37 instance C_Select Ent38 Ent31 where _select = Select_38 [] select_ = Select_38 instance C_Select Ent39 Ent31 where _select = Select_39 [] select_ = Select_39 instance C_Select Ent40 Ent31 where _select = Select_40 [] select_ = Select_40 instance C_Select Ent41 Ent31 where _select = Select_41 [] select_ = Select_41 instance C_Select Ent42 Ent31 where _select = Select_42 [] select_ = Select_42 instance C_Select Ent43 Ent31 where _select = Select_43 [] select_ = Select_43 instance C_Select Ent44 Ent31 where _select = Select_44 [] select_ = Select_44 instance C_Select Ent45 Ent31 where _select = Select_45 [] select_ = Select_45 instance C_Select Ent46 Ent31 where _select = Select_46 [] select_ = Select_46 instance C_Select Ent47 Ent31 where _select = Select_47 [] select_ = Select_47 instance C_Select Ent48 Ent31 where _select = Select_48 [] select_ = Select_48 instance C_Select Ent49 Ent31 where _select = Select_49 [] select_ = Select_49 class C_Optgroup a b | a -> b where _optgroup :: [b] -> a optgroup_ :: [Att48] -> [b] -> a instance C_Optgroup Ent31 Ent32 where _optgroup = Optgroup_31 [] optgroup_ = Optgroup_31 class C_Option a b | a -> b where _option :: [b] -> a option_ :: [Att50] -> [b] -> a instance C_Option Ent31 Ent2 where _option = Option_31 [] option_ = Option_31 instance C_Option Ent32 Ent2 where _option = Option_32 [] option_ = Option_32 class C_Textarea a b | a -> b where _textarea :: [b] -> a textarea_ :: [Att51] -> [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 Ent8 Ent2 where _textarea = Textarea_8 [] textarea_ = Textarea_8 instance C_Textarea Ent9 Ent2 where _textarea = Textarea_9 [] textarea_ = Textarea_9 instance C_Textarea Ent10 Ent2 where _textarea = Textarea_10 [] textarea_ = Textarea_10 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 Ent13 Ent2 where _textarea = Textarea_13 [] textarea_ = Textarea_13 instance C_Textarea Ent14 Ent2 where _textarea = Textarea_14 [] textarea_ = Textarea_14 instance C_Textarea Ent15 Ent2 where _textarea = Textarea_15 [] textarea_ = Textarea_15 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 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 Ent27 Ent2 where _textarea = Textarea_27 [] textarea_ = Textarea_27 instance C_Textarea Ent28 Ent2 where _textarea = Textarea_28 [] textarea_ = Textarea_28 instance C_Textarea Ent29 Ent2 where _textarea = Textarea_29 [] textarea_ = Textarea_29 instance C_Textarea Ent30 Ent2 where _textarea = Textarea_30 [] textarea_ = Textarea_30 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 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 Ent42 Ent2 where _textarea = Textarea_42 [] textarea_ = Textarea_42 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 instance C_Textarea Ent48 Ent2 where _textarea = Textarea_48 [] textarea_ = Textarea_48 instance C_Textarea Ent49 Ent2 where _textarea = Textarea_49 [] textarea_ = Textarea_49 class C_Fieldset a b | a -> b where _fieldset :: [b] -> a fieldset_ :: [Att10] -> [b] -> a instance C_Fieldset Ent3 Ent49 where _fieldset = Fieldset_3 [] fieldset_ = Fieldset_3 instance C_Fieldset Ent4 Ent49 where _fieldset = Fieldset_4 [] fieldset_ = Fieldset_4 instance C_Fieldset Ent11 Ent20 where _fieldset = Fieldset_11 [] fieldset_ = Fieldset_11 instance C_Fieldset Ent14 Ent15 where _fieldset = Fieldset_14 [] fieldset_ = Fieldset_14 instance C_Fieldset Ent15 Ent15 where _fieldset = Fieldset_15 [] fieldset_ = Fieldset_15 instance C_Fieldset Ent20 Ent20 where _fieldset = Fieldset_20 [] fieldset_ = Fieldset_20 instance C_Fieldset Ent21 Ent20 where _fieldset = Fieldset_21 [] fieldset_ = Fieldset_21 instance C_Fieldset Ent22 Ent20 where _fieldset = Fieldset_22 [] fieldset_ = Fieldset_22 instance C_Fieldset Ent24 Ent29 where _fieldset = Fieldset_24 [] fieldset_ = Fieldset_24 instance C_Fieldset Ent27 Ent28 where _fieldset = Fieldset_27 [] fieldset_ = Fieldset_27 instance C_Fieldset Ent28 Ent28 where _fieldset = Fieldset_28 [] fieldset_ = Fieldset_28 instance C_Fieldset Ent29 Ent29 where _fieldset = Fieldset_29 [] fieldset_ = Fieldset_29 instance C_Fieldset Ent30 Ent29 where _fieldset = Fieldset_30 [] fieldset_ = Fieldset_30 instance C_Fieldset Ent34 Ent45 where _fieldset = Fieldset_34 [] fieldset_ = Fieldset_34 instance C_Fieldset Ent35 Ent15 where _fieldset = Fieldset_35 [] fieldset_ = Fieldset_35 instance C_Fieldset Ent36 Ent15 where _fieldset = Fieldset_36 [] fieldset_ = Fieldset_36 instance C_Fieldset Ent37 Ent28 where _fieldset = Fieldset_37 [] fieldset_ = Fieldset_37 instance C_Fieldset Ent38 Ent45 where _fieldset = Fieldset_38 [] fieldset_ = Fieldset_38 instance C_Fieldset Ent40 Ent43 where _fieldset = Fieldset_40 [] fieldset_ = Fieldset_40 instance C_Fieldset Ent43 Ent43 where _fieldset = Fieldset_43 [] fieldset_ = Fieldset_43 instance C_Fieldset Ent44 Ent43 where _fieldset = Fieldset_44 [] fieldset_ = Fieldset_44 instance C_Fieldset Ent45 Ent45 where _fieldset = Fieldset_45 [] fieldset_ = Fieldset_45 instance C_Fieldset Ent46 Ent47 where _fieldset = Fieldset_46 [] fieldset_ = Fieldset_46 instance C_Fieldset Ent47 Ent47 where _fieldset = Fieldset_47 [] fieldset_ = Fieldset_47 instance C_Fieldset Ent48 Ent47 where _fieldset = Fieldset_48 [] fieldset_ = Fieldset_48 instance C_Fieldset Ent49 Ent49 where _fieldset = Fieldset_49 [] fieldset_ = Fieldset_49 class C_Legend a b | a -> b where _legend :: [b] -> a legend_ :: [Att54] -> [b] -> a instance C_Legend Ent15 Ent10 where _legend = Legend_15 [] legend_ = Legend_15 instance C_Legend Ent20 Ent10 where _legend = Legend_20 [] legend_ = Legend_20 instance C_Legend Ent28 Ent23 where _legend = Legend_28 [] legend_ = Legend_28 instance C_Legend Ent29 Ent23 where _legend = Legend_29 [] legend_ = Legend_29 instance C_Legend Ent43 Ent39 where _legend = Legend_43 [] legend_ = Legend_43 instance C_Legend Ent45 Ent5 where _legend = Legend_45 [] legend_ = Legend_45 instance C_Legend Ent47 Ent39 where _legend = Legend_47 [] legend_ = Legend_47 instance C_Legend Ent49 Ent5 where _legend = Legend_49 [] legend_ = Legend_49 class C_Button a b | a -> b where _button :: [b] -> a button_ :: [Att55] -> [b] -> a instance C_Button Ent3 Ent33 where _button = Button_3 [] button_ = Button_3 instance C_Button Ent4 Ent33 where _button = Button_4 [] button_ = Button_4 instance C_Button Ent5 Ent33 where _button = Button_5 [] button_ = Button_5 instance C_Button Ent8 Ent33 where _button = Button_8 [] button_ = Button_8 instance C_Button Ent9 Ent33 where _button = Button_9 [] button_ = Button_9 instance C_Button Ent10 Ent33 where _button = Button_10 [] button_ = Button_10 instance C_Button Ent11 Ent33 where _button = Button_11 [] button_ = Button_11 instance C_Button Ent12 Ent33 where _button = Button_12 [] button_ = Button_12 instance C_Button Ent13 Ent33 where _button = Button_13 [] button_ = Button_13 instance C_Button Ent14 Ent33 where _button = Button_14 [] button_ = Button_14 instance C_Button Ent15 Ent33 where _button = Button_15 [] button_ = Button_15 instance C_Button Ent20 Ent33 where _button = Button_20 [] button_ = Button_20 instance C_Button Ent21 Ent33 where _button = Button_21 [] button_ = Button_21 instance C_Button Ent23 Ent33 where _button = Button_23 [] button_ = Button_23 instance C_Button Ent24 Ent33 where _button = Button_24 [] button_ = Button_24 instance C_Button Ent25 Ent33 where _button = Button_25 [] button_ = Button_25 instance C_Button Ent26 Ent33 where _button = Button_26 [] button_ = Button_26 instance C_Button Ent27 Ent33 where _button = Button_27 [] button_ = Button_27 instance C_Button Ent28 Ent33 where _button = Button_28 [] button_ = Button_28 instance C_Button Ent29 Ent33 where _button = Button_29 [] button_ = Button_29 instance C_Button Ent30 Ent33 where _button = Button_30 [] button_ = Button_30 instance C_Button Ent34 Ent33 where _button = Button_34 [] button_ = Button_34 instance C_Button Ent35 Ent33 where _button = Button_35 [] button_ = Button_35 instance C_Button Ent37 Ent33 where _button = Button_37 [] button_ = Button_37 instance C_Button Ent38 Ent33 where _button = Button_38 [] button_ = Button_38 instance C_Button Ent39 Ent33 where _button = Button_39 [] button_ = Button_39 instance C_Button Ent40 Ent33 where _button = Button_40 [] button_ = Button_40 instance C_Button Ent41 Ent33 where _button = Button_41 [] button_ = Button_41 instance C_Button Ent42 Ent33 where _button = Button_42 [] button_ = Button_42 instance C_Button Ent43 Ent33 where _button = Button_43 [] button_ = Button_43 instance C_Button Ent44 Ent33 where _button = Button_44 [] button_ = Button_44 instance C_Button Ent45 Ent33 where _button = Button_45 [] button_ = Button_45 instance C_Button Ent46 Ent33 where _button = Button_46 [] button_ = Button_46 instance C_Button Ent47 Ent33 where _button = Button_47 [] button_ = Button_47 instance C_Button Ent48 Ent33 where _button = Button_48 [] button_ = Button_48 instance C_Button Ent49 Ent33 where _button = Button_49 [] button_ = Button_49 class C_Isindex a where _isindex :: a isindex_ :: [Att56] -> a instance C_Isindex Ent1 where _isindex = Isindex_1 [] isindex_ = Isindex_1 instance C_Isindex Ent3 where _isindex = Isindex_3 [] isindex_ = Isindex_3 instance C_Isindex Ent4 where _isindex = Isindex_4 [] isindex_ = Isindex_4 instance C_Isindex Ent11 where _isindex = Isindex_11 [] isindex_ = Isindex_11 instance C_Isindex Ent14 where _isindex = Isindex_14 [] isindex_ = Isindex_14 instance C_Isindex Ent15 where _isindex = Isindex_15 [] isindex_ = Isindex_15 instance C_Isindex Ent20 where _isindex = Isindex_20 [] isindex_ = Isindex_20 instance C_Isindex Ent21 where _isindex = Isindex_21 [] isindex_ = Isindex_21 instance C_Isindex Ent22 where _isindex = Isindex_22 [] isindex_ = Isindex_22 instance C_Isindex Ent24 where _isindex = Isindex_24 [] isindex_ = Isindex_24 instance C_Isindex Ent27 where _isindex = Isindex_27 [] isindex_ = Isindex_27 instance C_Isindex Ent28 where _isindex = Isindex_28 [] isindex_ = Isindex_28 instance C_Isindex Ent29 where _isindex = Isindex_29 [] isindex_ = Isindex_29 instance C_Isindex Ent30 where _isindex = Isindex_30 [] isindex_ = Isindex_30 instance C_Isindex Ent34 where _isindex = Isindex_34 [] isindex_ = Isindex_34 instance C_Isindex Ent35 where _isindex = Isindex_35 [] isindex_ = Isindex_35 instance C_Isindex Ent36 where _isindex = Isindex_36 [] isindex_ = Isindex_36 instance C_Isindex Ent37 where _isindex = Isindex_37 [] isindex_ = Isindex_37 instance C_Isindex Ent38 where _isindex = Isindex_38 [] isindex_ = Isindex_38 instance C_Isindex Ent40 where _isindex = Isindex_40 [] isindex_ = Isindex_40 instance C_Isindex Ent43 where _isindex = Isindex_43 [] isindex_ = Isindex_43 instance C_Isindex Ent44 where _isindex = Isindex_44 [] isindex_ = Isindex_44 instance C_Isindex Ent45 where _isindex = Isindex_45 [] isindex_ = Isindex_45 instance C_Isindex Ent46 where _isindex = Isindex_46 [] isindex_ = Isindex_46 instance C_Isindex Ent47 where _isindex = Isindex_47 [] isindex_ = Isindex_47 instance C_Isindex Ent48 where _isindex = Isindex_48 [] isindex_ = Isindex_48 instance C_Isindex Ent49 where _isindex = Isindex_49 [] isindex_ = Isindex_49 class C_Table a b | a -> b where _table :: [b] -> a table_ :: [Att57] -> [b] -> a instance C_Table Ent3 Ent16 where _table = Table_3 [] table_ = Table_3 instance C_Table Ent4 Ent16 where _table = Table_4 [] table_ = Table_4 instance C_Table Ent11 Ent16 where _table = Table_11 [] table_ = Table_11 instance C_Table Ent14 Ent16 where _table = Table_14 [] table_ = Table_14 instance C_Table Ent15 Ent16 where _table = Table_15 [] table_ = Table_15 instance C_Table Ent20 Ent16 where _table = Table_20 [] table_ = Table_20 instance C_Table Ent21 Ent16 where _table = Table_21 [] table_ = Table_21 instance C_Table Ent22 Ent16 where _table = Table_22 [] table_ = Table_22 instance C_Table Ent24 Ent16 where _table = Table_24 [] table_ = Table_24 instance C_Table Ent27 Ent16 where _table = Table_27 [] table_ = Table_27 instance C_Table Ent28 Ent16 where _table = Table_28 [] table_ = Table_28 instance C_Table Ent29 Ent16 where _table = Table_29 [] table_ = Table_29 instance C_Table Ent30 Ent16 where _table = Table_30 [] table_ = Table_30 instance C_Table Ent33 Ent16 where _table = Table_33 [] table_ = Table_33 instance C_Table Ent34 Ent16 where _table = Table_34 [] table_ = Table_34 instance C_Table Ent35 Ent16 where _table = Table_35 [] table_ = Table_35 instance C_Table Ent36 Ent16 where _table = Table_36 [] table_ = Table_36 instance C_Table Ent37 Ent16 where _table = Table_37 [] table_ = Table_37 instance C_Table Ent38 Ent16 where _table = Table_38 [] table_ = Table_38 instance C_Table Ent40 Ent16 where _table = Table_40 [] table_ = Table_40 instance C_Table Ent43 Ent16 where _table = Table_43 [] table_ = Table_43 instance C_Table Ent44 Ent16 where _table = Table_44 [] table_ = Table_44 instance C_Table Ent45 Ent16 where _table = Table_45 [] table_ = Table_45 instance C_Table Ent46 Ent16 where _table = Table_46 [] table_ = Table_46 instance C_Table Ent47 Ent16 where _table = Table_47 [] table_ = Table_47 instance C_Table Ent48 Ent16 where _table = Table_48 [] table_ = Table_48 instance C_Table Ent49 Ent16 where _table = Table_49 [] table_ = Table_49 class C_Caption a b | a -> b where _caption :: [b] -> a caption_ :: [Att15] -> [b] -> a instance C_Caption Ent16 Ent10 where _caption = Caption_16 [] caption_ = Caption_16 class C_Thead a b | a -> b where _thead :: [b] -> a thead_ :: [Att58] -> [b] -> a instance C_Thead Ent16 Ent17 where _thead = Thead_16 [] thead_ = Thead_16 class C_Tfoot a b | a -> b where _tfoot :: [b] -> a tfoot_ :: [Att58] -> [b] -> a instance C_Tfoot Ent16 Ent17 where _tfoot = Tfoot_16 [] tfoot_ = Tfoot_16 class C_Tbody a b | a -> b where _tbody :: [b] -> a tbody_ :: [Att58] -> [b] -> a instance C_Tbody Ent16 Ent17 where _tbody = Tbody_16 [] tbody_ = Tbody_16 class C_Colgroup a b | a -> b where _colgroup :: [b] -> a colgroup_ :: [Att59] -> [b] -> a instance C_Colgroup Ent16 Ent18 where _colgroup = Colgroup_16 [] colgroup_ = Colgroup_16 class C_Col a where _col :: a col_ :: [Att59] -> a instance C_Col Ent16 where _col = Col_16 [] col_ = Col_16 instance C_Col Ent18 where _col = Col_18 [] col_ = Col_18 class C_Tr a b | a -> b where _tr :: [b] -> a tr_ :: [Att60] -> [b] -> a instance C_Tr Ent16 Ent19 where _tr = Tr_16 [] tr_ = Tr_16 instance C_Tr Ent17 Ent19 where _tr = Tr_17 [] tr_ = Tr_17 class C_Th a b | a -> b where _th :: [b] -> a th_ :: [Att61] -> [b] -> a instance C_Th Ent19 Ent14 where _th = Th_19 [] th_ = Th_19 class C_Td a b | a -> b where _td :: [b] -> a td_ :: [Att61] -> [b] -> a instance C_Td Ent19 Ent14 where _td = Td_19 [] td_ = Td_19 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 Ent8 where pcdata s = PCDATA_8 [] (s2b_escape s) pcdata_bs = PCDATA_8 [] instance C_PCDATA Ent9 where pcdata s = PCDATA_9 [] (s2b_escape s) pcdata_bs = PCDATA_9 [] instance C_PCDATA Ent10 where pcdata s = PCDATA_10 [] (s2b_escape s) pcdata_bs = PCDATA_10 [] 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 Ent13 where pcdata s = PCDATA_13 [] (s2b_escape s) pcdata_bs = PCDATA_13 [] instance C_PCDATA Ent14 where pcdata s = PCDATA_14 [] (s2b_escape s) pcdata_bs = PCDATA_14 [] instance C_PCDATA Ent15 where pcdata s = PCDATA_15 [] (s2b_escape s) pcdata_bs = PCDATA_15 [] 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 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 Ent27 where pcdata s = PCDATA_27 [] (s2b_escape s) pcdata_bs = PCDATA_27 [] instance C_PCDATA Ent28 where pcdata s = PCDATA_28 [] (s2b_escape s) pcdata_bs = PCDATA_28 [] 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 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 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 Ent42 where pcdata s = PCDATA_42 [] (s2b_escape s) pcdata_bs = PCDATA_42 [] 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 [] instance C_PCDATA Ent48 where pcdata s = PCDATA_48 [] (s2b_escape s) pcdata_bs = PCDATA_48 [] instance C_PCDATA Ent49 where pcdata s = PCDATA_49 [] (s2b_escape s) pcdata_bs = PCDATA_49 [] 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 (Frameset_0 att c) = B.concat [frameset_byte_b,renderAtts att,gt_byte, maprender c,frameset_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] render_bs (Isindex_1 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_3 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_3 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_3 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_3 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_3 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_3 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_3 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_3 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_3 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_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 (Applet_3 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] 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 (Isindex_3 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Noscript_4 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_4 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_4 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_4 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_4 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_4 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_4 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_4 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_4 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_4 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_4 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_4 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_4 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_4 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_4 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_4 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_4 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_4 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_4 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_4 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (A_4 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_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 (U_4 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_4 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_4 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_4 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_4 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_4 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_4 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_4 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_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 (Fieldset_4 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_4 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_4 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_4 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_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 (Iframe_5 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (A_5 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_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 (U_5 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_5 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_5 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_5 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_5 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_5 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_5 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (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 (Button_5 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_5 _ str) = str instance Render Ent6 where render_bs (Li_6 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e] instance Render Ent7 where render_bs (Dt_7 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e] render_bs (Dd_7 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e] instance Render Ent8 where render_bs (Script_8 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Iframe_8 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (P_8 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (Ins_8 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_8 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_8 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_8 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_8 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_8 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_8 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_8 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_8 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_8 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_8 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_8 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_8 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_8 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_8 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_8 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_8 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_8 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_8 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_8 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_8 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_8 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_8 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_8 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_8 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_8 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_8 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_8 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_8 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_8 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_8 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_8 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_8 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_8 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_8 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_8 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_8 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_8 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_8 _ str) = str 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 (A_9 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_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 (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 (U_9 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_9 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_9 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_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 (Iframe_10 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Ins_10 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_10 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_10 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_10 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_10 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_10 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_10 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_10 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_10 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_10 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_10 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_10 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_10 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_10 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_10 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_10 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_10 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_10 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_10 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_10 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_10 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_10 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_10 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_10 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_10 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_10 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_10 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_10 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_10 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_10 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_10 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_10 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_10 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_10 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_10 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_10 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_10 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_10 _ str) = str instance Render Ent11 where render_bs (Script_11 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_11 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_11 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_11 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_11 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_11 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_11 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_11 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_11 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_11 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_11 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_11 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_11 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_11 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_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 (Isindex_11 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_12 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (P_12 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_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 (U_12 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_12 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_12 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_12 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_12 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_12 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_12 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Button_12 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_12 _ str) = str instance Render Ent13 where render_bs (Script_13 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Ins_13 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_13 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_13 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_13 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_13 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_13 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_13 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_13 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_13 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_13 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_13 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_13 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_13 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_13 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_13 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_13 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Tt_13 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_13 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_13 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (U_13 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_13 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_13 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Label_13 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_13 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_13 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_13 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_13 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_13 _ str) = str instance Render Ent14 where render_bs (Script_14 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_14 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_14 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_14 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_14 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_14 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_14 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_14 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_14 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_14 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_14 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_14 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_14 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_14 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_14 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_14 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_14 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_14 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_14 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_14 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_14 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_byte_e] render_bs (Ins_14 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_14 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_14 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_14 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_14 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_14 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_14 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_14 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_14 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_14 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_14 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_14 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_14 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_14 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_14 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_14 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_14 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_14 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_14 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_14 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_14 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_14 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_14 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_14 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_14 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_14 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_14 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_14 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_14 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_14 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_14 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_14 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_14 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_14 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_14 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_14 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_14 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_14 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_14 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_14 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_14 _ str) = str instance Render Ent15 where render_bs (Script_15 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_15 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_15 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_15 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_15 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_15 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_15 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_15 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_15 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_15 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_15 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_15 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_15 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_15 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_15 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_15 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_15 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_15 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_15 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_15 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_15 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_byte_e] render_bs (Ins_15 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_15 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_15 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_15 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_15 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_15 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_15 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_15 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_15 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_15 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_15 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_15 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_15 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_15 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_15 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_15 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_15 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_15 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_15 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_15 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_15 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_15 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_15 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_15 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_15 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_15 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_15 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_15 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_15 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_15 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_15 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_15 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Label_15 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_15 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_15 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_15 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_15 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_15 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_15 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_15 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_15 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_15 _ str) = str instance Render Ent16 where render_bs (Caption_16 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e] render_bs (Thead_16 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e] render_bs (Tfoot_16 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e] render_bs (Tbody_16 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e] render_bs (Colgroup_16 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e] render_bs (Col_16 att) = B.concat [col_byte_b,renderAtts att,gts_byte] render_bs (Tr_16 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e] instance Render Ent17 where render_bs (Tr_17 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e] instance Render Ent18 where render_bs (Col_18 att) = B.concat [col_byte_b,renderAtts att,gts_byte] instance Render Ent19 where render_bs (Th_19 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e] render_bs (Td_19 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_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 (Noscript_20 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_20 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_20 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_20 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_20 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_20 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_20 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_20 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_20 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_20 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_20 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_20 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_20 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_20 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_20 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_20 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_20 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_20 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_20 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_20 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_20 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_20 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_20 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_20 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_20 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_20 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_20 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_20 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_20 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_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 (Fieldset_20 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_20 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_20 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_20 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_20 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_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 (Iframe_21 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_21 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_21 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_21 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_21 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_21 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_21 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_21 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_21 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_21 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_21 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Applet_21 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Label_21 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_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 (Isindex_21 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Noscript_22 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_22 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_22 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_22 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_22 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_22 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_22 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_22 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_22 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_22 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_22 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_22 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_22 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_22 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_22 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_22 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_22 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_22 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_22 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (Area_22 att) = B.concat [area_byte_b,renderAtts att,gts_byte] render_bs (Form_22 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Fieldset_22 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Isindex_22 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_22 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] 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 (Iframe_23 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (U_23 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_23 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_23 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_23 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_23 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_23 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_23 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Button_23 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_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 (Iframe_24 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_24 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_24 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_24 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_24 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_24 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_24 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_24 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_24 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_24 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_24 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_24 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_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 (Button_24 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_24 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_25 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (P_25 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_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 (U_25 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_25 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_25 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_25 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_25 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_25 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_25 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (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 (Button_25 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_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 (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 (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 (U_26 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_26 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_26 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_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 (Button_26 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_26 _ str) = str instance Render Ent27 where render_bs (Script_27 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_27 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_27 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_27 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_27 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_27 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_27 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_27 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_27 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_27 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_27 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_27 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_27 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_27 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_27 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_27 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_27 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_27 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_27 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_27 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_27 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_byte_e] render_bs (Ins_27 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_27 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_27 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_27 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_27 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_27 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_27 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_27 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_27 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_27 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_27 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_27 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_27 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_27 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_27 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_27 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_27 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_27 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_27 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_27 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_27 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_27 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_27 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_27 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_27 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_27 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_27 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_27 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_27 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_27 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_27 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_27 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_27 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_27 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_27 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_27 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_27 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_27 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_27 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_27 _ str) = str instance Render Ent28 where render_bs (Script_28 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_28 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_28 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_28 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_28 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_28 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_28 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_28 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_28 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_28 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_28 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_28 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_28 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_28 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_28 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_28 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_28 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_28 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_28 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_28 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_28 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_byte_e] render_bs (Ins_28 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_28 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (Span_28 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_28 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_28 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_28 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_28 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_28 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_28 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_28 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_28 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_28 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_28 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_28 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_28 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_28 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_28 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_28 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_28 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_28 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_28 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_28 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_28 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_28 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_28 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_28 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_28 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_28 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_28 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_28 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_28 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_28 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Input_28 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_28 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_28 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_28 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_28 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_28 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_28 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_28 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_28 _ str) = str instance Render Ent29 where render_bs (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 (Iframe_29 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_29 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_29 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_29 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_29 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_29 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_29 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_29 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_29 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_29 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_29 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_29 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_29 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_29 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_29 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_29 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_29 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_29 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_29 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Noscript_30 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_30 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_30 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_30 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_30 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_30 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_30 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_30 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_30 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_30 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_30 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_30 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_30 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_30 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_30 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_30 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_30 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_30 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_30 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_30 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (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 (U_30 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_30 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_30 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_30 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_30 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_30 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_30 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Applet_30 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_30 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_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 (Fieldset_30 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_30 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_30 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_30 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_30 _ str) = str instance Render Ent31 where render_bs (Optgroup_31 att c) = B.concat [optgroup_byte_b,renderAtts att,gt_byte, maprender c,optgroup_byte_e] render_bs (Option_31 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent32 where render_bs (Option_32 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e] instance Render Ent33 where render_bs (Script_33 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_33 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Div_33 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_33 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_33 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_33 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_33 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_33 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_33 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_33 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_33 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_33 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_33 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_33 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_33 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_33 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_33 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_33 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_33 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_33 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (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 (U_33 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_33 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_33 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_33 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_33 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_33 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_33 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_33 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_33 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Table_33 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_33 _ str) = str instance Render Ent34 where render_bs (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 (Iframe_34 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_34 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_34 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_34 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_34 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_34 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_34 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_34 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_34 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_34 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_34 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Label_34 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_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 (Isindex_34 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_35 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_35 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_35 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_35 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (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 (U_35 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_35 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_35 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_35 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_35 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_35 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_35 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Applet_35 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Label_35 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_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 (Button_35 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_35 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Menu_36 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_36 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_36 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (Area_36 att) = B.concat [area_byte_b,renderAtts att,gts_byte] render_bs (Fieldset_36 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Isindex_36 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_36 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] 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 (Iframe_37 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_37 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_37 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_37 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (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 (U_37 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_37 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_37 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_37 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_37 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_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 (Applet_37 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] 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 (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 (Isindex_37 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_38 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_38 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_38 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_38 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_38 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_38 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_38 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_38 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_38 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_38 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_38 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Applet_38 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (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 (Isindex_38 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_39 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (U_39 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_39 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_39 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_39 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_39 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_39 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_39 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_39 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_39 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_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 (Iframe_40 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_40 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_40 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_40 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_40 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_40 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_40 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_40 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_40 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_40 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_40 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (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 (Isindex_40 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_41 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (P_41 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_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 (A_41 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_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 (U_41 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_41 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_41 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_41 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_41 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_41 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_41 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] 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 (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 (Button_41 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_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 (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 (A_42 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_42 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_42 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_42 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_42 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_42 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_42 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_42 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_42 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_42 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_42 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_42 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_42 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_42 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_42 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Tt_42 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_42 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_42 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (U_42 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_42 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_42 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Input_42 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_42 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_42 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Button_42 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (PCDATA_42 _ str) = str 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 (Iframe_43 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_43 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_43 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_43 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (A_43 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_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 (U_43 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_43 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_43 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_43 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_43 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_43 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_43 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] 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 (Legend_43 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_43 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_43 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_44 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_44 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_44 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_44 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_44 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_44 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_44 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_44 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_44 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_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 (Applet_44 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] 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 (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 (Isindex_44 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_45 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_45 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_45 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_45 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_45 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_45 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_45 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_45 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_45 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_45 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_45 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] 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 (Label_45 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_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 (Legend_45 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_45 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_45 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_46 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_46 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_46 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_46 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_46 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_46 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_46 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_46 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_46 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_46 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_46 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (Form_46 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_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 (Button_46 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_46 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 (Iframe_47 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_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 (Menu_47 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_47 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_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 (Center_47 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_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 (U_47 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_47 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_47 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_47 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_47 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_47 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_47 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_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 (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 (Isindex_47 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] 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 instance Render Ent48 where render_bs (Script_48 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_48 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_48 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_48 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_48 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_48 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_48 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_48 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_48 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_48 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_48 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_48 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_48 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_48 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_48 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_48 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_48 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_48 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_48 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_48 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_48 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_byte_e] render_bs (Ins_48 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_48 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_48 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_48 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_48 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_48 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_48 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_48 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_48 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_48 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_48 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_48 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_48 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_48 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_48 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_48 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_48 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_48 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_48 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_48 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_48 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_48 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_48 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_48 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_48 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_48 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_48 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_48 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_48 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_48 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Param_48 att) = B.concat [param_byte_b,renderAtts att,gts_byte] render_bs (Applet_48 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_48 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_48 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_48 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Input_48 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_48 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_48 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_48 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Button_48 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_48 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_48 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_48 _ str) = str instance Render Ent49 where render_bs (Script_49 att c) = B.concat [script_byte_b,renderAtts att,gt_byte, maprender c,script_byte_e] render_bs (Noscript_49 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e] render_bs (Iframe_49 att c) = B.concat [iframe_byte_b,renderAtts att,gt_byte, maprender c,iframe_byte_e] render_bs (Div_49 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e] render_bs (P_49 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e] render_bs (H1_49 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e] render_bs (H2_49 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e] render_bs (H3_49 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e] render_bs (H4_49 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e] render_bs (H5_49 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e] render_bs (H6_49 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e] render_bs (Ul_49 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e] render_bs (Ol_49 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e] render_bs (Menu_49 att c) = B.concat [menu_byte_b,renderAtts att,gt_byte, maprender c,menu_byte_e] render_bs (Dir_49 att c) = B.concat [dir_byte_b,renderAtts att,gt_byte, maprender c,dir_byte_e] render_bs (Dl_49 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e] render_bs (Address_49 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e] render_bs (Hr_49 att) = B.concat [hr_byte_b,renderAtts att,gts_byte] render_bs (Pre_49 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e] render_bs (Blockquote_49 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e] render_bs (Center_49 att c) = B.concat [center_byte_b,renderAtts att,gt_byte, maprender c,center_byte_e] render_bs (Ins_49 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e] render_bs (Del_49 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e] render_bs (A_49 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e] render_bs (Span_49 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e] render_bs (Bdo_49 att c) = B.concat [bdo_byte_b,renderAtts att,gt_byte, maprender c,bdo_byte_e] render_bs (Br_49 att) = B.concat [br_byte_b,renderAtts att,gts_byte] render_bs (Em_49 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e] render_bs (Strong_49 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e] render_bs (Dfn_49 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e] render_bs (Code_49 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e] render_bs (Samp_49 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e] render_bs (Kbd_49 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e] render_bs (Var_49 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e] render_bs (Cite_49 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e] render_bs (Abbr_49 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e] render_bs (Acronym_49 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e] render_bs (Q_49 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e] render_bs (Sub_49 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e] render_bs (Sup_49 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e] render_bs (Tt_49 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e] render_bs (I_49 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e] render_bs (B_49 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e] render_bs (Big_49 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e] render_bs (Small_49 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e] render_bs (U_49 att c) = B.concat [u_byte_b,renderAtts att,gt_byte, maprender c,u_byte_e] render_bs (S_49 att c) = B.concat [s_byte_b,renderAtts att,gt_byte, maprender c,s_byte_e] render_bs (Strike_49 att c) = B.concat [strike_byte_b,renderAtts att,gt_byte, maprender c,strike_byte_e] render_bs (Basefont_49 att) = B.concat [basefont_byte_b,renderAtts att,gts_byte] render_bs (Font_49 att c) = B.concat [font_byte_b,renderAtts att,gt_byte, maprender c,font_byte_e] render_bs (Object_49 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e] render_bs (Applet_49 att c) = B.concat [applet_byte_b,renderAtts att,gt_byte, maprender c,applet_byte_e] render_bs (Img_49 att) = B.concat [img_byte_b,renderAtts att,gts_byte] render_bs (Map_49 att c) = B.concat [map_byte_b,renderAtts att,gt_byte, maprender c,map_byte_e] render_bs (Form_49 att c) = B.concat [form_byte_b,renderAtts att,gt_byte, maprender c,form_byte_e] render_bs (Label_49 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e] render_bs (Input_49 att) = B.concat [input_byte_b,renderAtts att,gts_byte] render_bs (Select_49 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e] render_bs (Textarea_49 att c) = B.concat [textarea_byte_b,renderAtts att,gt_byte, maprender c,textarea_byte_e] render_bs (Fieldset_49 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e] render_bs (Legend_49 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e] render_bs (Button_49 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e] render_bs (Isindex_49 att) = B.concat [isindex_byte_b,renderAtts att,gts_byte] render_bs (Table_49 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e] render_bs (PCDATA_49 _ str) = str instance Render Ent50 where render_bs (Frameset_50 att c) = B.concat [frameset_byte_b,renderAtts att,gt_byte, maprender c,frameset_byte_e] render_bs (Frame_50 att) = B.concat [frame_byte_b,renderAtts att,gts_byte] render_bs (Noframes_50 att c) = B.concat [noframes_byte_b,renderAtts att,gt_byte, maprender c,noframes_byte_e] instance Render Ent51 where render_bs (Body_51 att c) = B.concat [body_byte_b,renderAtts att,gt_byte, maprender c,body_byte_e] none_byte_b = s2b "\n" cdata_byte_b = s2b "\n" pcdata_byte_b = s2b "\n" td_byte_b = s2b "\n" th_byte_b = s2b "\n" tr_byte_b = s2b "\n" col_byte_b = s2b "\n" colgroup_byte_b = s2b "\n" tbody_byte_b = s2b "\n" tfoot_byte_b = s2b "\n" thead_byte_b = s2b "\n" caption_byte_b = s2b "\n" table_byte_b = s2b "\n" isindex_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" applet_byte_b = s2b "\n" param_byte_b = s2b "\n" object_byte_b = s2b "\n" font_byte_b = s2b "\n" basefont_byte_b = s2b "\n" strike_byte_b = s2b "\n" s_byte_b = s2b "\n" u_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" center_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" dir_byte_b = s2b "\n" menu_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" noframes_byte_b = s2b "\n" iframe_byte_b = s2b "\n" frame_byte_b = s2b "\n" frameset_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" nohref_byte = s2b "nohref" onkeydown_byte = s2b "onkeydown" target_byte = s2b "target" onkeyup_byte = s2b "onkeyup" onreset_byte = s2b "onreset" tex_byte = s2b "tex" code_byte = s2b "code" valign_byte = s2b "valign" name_byte = s2b "name" charset_byte = s2b "charset" prompt_byte = s2b "prompt" accept_charset_byte = s2b "accept-charset" rev_byte = s2b "rev" title_byte = s2b "title" ge_byte = s2b "ge" start_byte = s2b "start" enctype_byte = s2b "enctype" usemap_byte = s2b "usemap" nowrap_byte = s2b "nowrap" coords_byte = s2b "coords" onblur_byte = s2b "onblur" datetime_byte = s2b "datetime" dir_byte = s2b "dir" color_byte = s2b "color" vspace_byte = s2b "vspace" x_www_form_urlencode_byte = s2b "x-www-form-urlencode" background_byte = s2b "background" height_byte = s2b "height" char_byte = s2b "char" codebase_byte = s2b "codebase" profile_byte = s2b "profile" rel_byte = s2b "rel" onsubmit_byte = s2b "onsubmit" marginwidth_byte = s2b "marginwidth" abbr_byte = s2b "abbr" onchange_byte = s2b "onchange" href_byte = s2b "href" id_byte = s2b "id" value_byte = s2b "value" aut_byte = s2b "aut" data_byte = s2b "data" declare_byte = s2b "declare" type_byte = s2b "type" headers_byte = s2b "headers" object_byte = s2b "object" noresize_byte = s2b "noresize" rowspan_byte = s2b "rowspan" defer_byte = s2b "defer" cellspacing_byte = s2b "cellspacing" charoff_byte = s2b "charoff" accept_byte = s2b "accept" alt_byte = s2b "alt" onmouseout_byte = s2b "onmouseout" border_byte = s2b "border" onunload_byte = s2b "onunload" cellpadding_byte = s2b "cellpadding" valuetype_byte = s2b "valuetype" content_byte = s2b "content" clear_byte = s2b "clear" onmouseup_byte = s2b "onmouseup" scope_byte = s2b "scope" onmouseover_byte = s2b "onmouseover" lang_byte = s2b "lang" align_byte = s2b "align" scheme_byte = s2b "scheme" frameborder_byte = s2b "frameborder" onmousedown_byte = s2b "onmousedown" onclick_byte = s2b "onclick" span_byte = s2b "span" width_byte = s2b "width" vlink_byte = s2b "vlink" ismap_byte = s2b "ismap" frame_byte = s2b "frame" size_byte = s2b "size" face_byte = s2b "face" bgcolor_byte = s2b "bgcolor" summary_byte = s2b "summary" text_byte = s2b "text" method_byte = s2b "method" language_byte = s2b "language" tabindex_byte = s2b "tabindex" standby_byte = s2b "standby" onmousemove_byte = s2b "onmousemove" style_byte = s2b "style" codetype_byte = s2b "codetype" non_byte = s2b "non" multiple_byte = s2b "multiple" xmlns_byte = s2b "xmlns" ondblclick_byte = s2b "ondblclick" axis_byte = s2b "axis" cols_byte = s2b "cols" readonly_byte = s2b "readonly" media_byte = s2b "media" compact_byte = s2b "compact" src_byte = s2b "src" for_byte = s2b "for" hreflang_byte = s2b "hreflang" checked_byte = s2b "checked" onkeypress_byte = s2b "onkeypress" class_byte = s2b "class" shape_byte = s2b "shape" label_byte = s2b "label" accesskey_byte = s2b "accesskey" disabled_byte = s2b "disabled" scrolling_byte = s2b "scrolling" rows_byte = s2b "rows" rules_byte = s2b "rules" onfocus_byte = s2b "onfocus" alink_byte = s2b "alink" colspan_byte = s2b "colspan" dat_byte = s2b "dat" cite_byte = s2b "cite" marginheight_byte = s2b "marginheight" link_byte = s2b "link" maxlength_byte = s2b "maxlength" onselect_byte = s2b "onselect" archive_byte = s2b "archive" longdesc_byte = s2b "longdesc" rec_byte = s2b "rec" classid_byte = s2b "classid" space_byte = s2b "space" noshade_byte = s2b "noshade" hspace_byte = s2b "hspace" onload_byte = s2b "onload" action_byte = s2b "action" submi_byte = s2b "submi" 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 (Frameset_0 _ _) = "frameset" 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" tagStr (Isindex_1 _) = "isindex" instance TagStr Ent2 where tagStr (PCDATA_2 _ _) = "PCDATA" instance TagStr Ent3 where tagStr (Script_3 _ _) = "script" tagStr (Noscript_3 _ _) = "noscript" tagStr (Iframe_3 _ _) = "iframe" 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 (Menu_3 _ _) = "menu" tagStr (Dir_3 _ _) = "dir" tagStr (Dl_3 _ _) = "dl" tagStr (Address_3 _ _) = "address" tagStr (Hr_3 _) = "hr" tagStr (Pre_3 _ _) = "pre" tagStr (Blockquote_3 _ _) = "blockquote" tagStr (Center_3 _ _) = "center" 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 (U_3 _ _) = "u" tagStr (S_3 _ _) = "s" tagStr (Strike_3 _ _) = "strike" tagStr (Basefont_3 _) = "basefont" tagStr (Font_3 _ _) = "font" tagStr (Object_3 _ _) = "object" tagStr (Param_3 _) = "param" tagStr (Applet_3 _ _) = "applet" 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 (Isindex_3 _) = "isindex" tagStr (Table_3 _ _) = "table" tagStr (PCDATA_3 _ _) = "PCDATA" instance TagStr Ent4 where tagStr (Script_4 _ _) = "script" tagStr (Noscript_4 _ _) = "noscript" tagStr (Iframe_4 _ _) = "iframe" tagStr (Div_4 _ _) = "div" tagStr (P_4 _ _) = "p" tagStr (H1_4 _ _) = "h1" tagStr (H2_4 _ _) = "h2" tagStr (H3_4 _ _) = "h3" tagStr (H4_4 _ _) = "h4" tagStr (H5_4 _ _) = "h5" tagStr (H6_4 _ _) = "h6" tagStr (Ul_4 _ _) = "ul" tagStr (Ol_4 _ _) = "ol" tagStr (Menu_4 _ _) = "menu" tagStr (Dir_4 _ _) = "dir" tagStr (Dl_4 _ _) = "dl" tagStr (Address_4 _ _) = "address" tagStr (Hr_4 _) = "hr" tagStr (Pre_4 _ _) = "pre" tagStr (Blockquote_4 _ _) = "blockquote" tagStr (Center_4 _ _) = "center" tagStr (Ins_4 _ _) = "ins" tagStr (Del_4 _ _) = "del" tagStr (A_4 _ _) = "a" 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 (U_4 _ _) = "u" tagStr (S_4 _ _) = "s" tagStr (Strike_4 _ _) = "strike" tagStr (Basefont_4 _) = "basefont" tagStr (Font_4 _ _) = "font" tagStr (Object_4 _ _) = "object" tagStr (Applet_4 _ _) = "applet" tagStr (Img_4 _) = "img" tagStr (Map_4 _ _) = "map" tagStr (Form_4 _ _) = "form" tagStr (Label_4 _ _) = "label" tagStr (Input_4 _) = "input" tagStr (Select_4 _ _) = "select" tagStr (Textarea_4 _ _) = "textarea" tagStr (Fieldset_4 _ _) = "fieldset" tagStr (Button_4 _ _) = "button" tagStr (Isindex_4 _) = "isindex" tagStr (Table_4 _ _) = "table" tagStr (PCDATA_4 _ _) = "PCDATA" instance TagStr Ent5 where tagStr (Script_5 _ _) = "script" tagStr (Iframe_5 _ _) = "iframe" tagStr (Ins_5 _ _) = "ins" tagStr (Del_5 _ _) = "del" tagStr (A_5 _ _) = "a" 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 (U_5 _ _) = "u" tagStr (S_5 _ _) = "s" tagStr (Strike_5 _ _) = "strike" tagStr (Basefont_5 _) = "basefont" tagStr (Font_5 _ _) = "font" tagStr (Object_5 _ _) = "object" tagStr (Applet_5 _ _) = "applet" tagStr (Img_5 _) = "img" tagStr (Map_5 _ _) = "map" tagStr (Label_5 _ _) = "label" tagStr (Input_5 _) = "input" tagStr (Select_5 _ _) = "select" tagStr (Textarea_5 _ _) = "textarea" tagStr (Button_5 _ _) = "button" tagStr (PCDATA_5 _ _) = "PCDATA" instance TagStr Ent6 where tagStr (Li_6 _ _) = "li" instance TagStr Ent7 where tagStr (Dt_7 _ _) = "dt" tagStr (Dd_7 _ _) = "dd" instance TagStr Ent8 where tagStr (Script_8 _ _) = "script" tagStr (Iframe_8 _ _) = "iframe" tagStr (P_8 _ _) = "p" tagStr (Ins_8 _ _) = "ins" tagStr (Del_8 _ _) = "del" tagStr (A_8 _ _) = "a" tagStr (Span_8 _ _) = "span" tagStr (Bdo_8 _ _) = "bdo" tagStr (Br_8 _) = "br" tagStr (Em_8 _ _) = "em" tagStr (Strong_8 _ _) = "strong" tagStr (Dfn_8 _ _) = "dfn" tagStr (Code_8 _ _) = "code" tagStr (Samp_8 _ _) = "samp" tagStr (Kbd_8 _ _) = "kbd" tagStr (Var_8 _ _) = "var" tagStr (Cite_8 _ _) = "cite" tagStr (Abbr_8 _ _) = "abbr" tagStr (Acronym_8 _ _) = "acronym" tagStr (Q_8 _ _) = "q" tagStr (Sub_8 _ _) = "sub" tagStr (Sup_8 _ _) = "sup" tagStr (Tt_8 _ _) = "tt" tagStr (I_8 _ _) = "i" tagStr (B_8 _ _) = "b" tagStr (Big_8 _ _) = "big" tagStr (Small_8 _ _) = "small" tagStr (U_8 _ _) = "u" tagStr (S_8 _ _) = "s" tagStr (Strike_8 _ _) = "strike" tagStr (Basefont_8 _) = "basefont" tagStr (Font_8 _ _) = "font" tagStr (Object_8 _ _) = "object" tagStr (Applet_8 _ _) = "applet" tagStr (Img_8 _) = "img" tagStr (Map_8 _ _) = "map" tagStr (Label_8 _ _) = "label" tagStr (Input_8 _) = "input" tagStr (Select_8 _ _) = "select" tagStr (Textarea_8 _ _) = "textarea" tagStr (Button_8 _ _) = "button" tagStr (PCDATA_8 _ _) = "PCDATA" instance TagStr Ent9 where tagStr (Script_9 _ _) = "script" tagStr (Ins_9 _ _) = "ins" tagStr (Del_9 _ _) = "del" tagStr (A_9 _ _) = "a" 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 (Tt_9 _ _) = "tt" tagStr (I_9 _ _) = "i" tagStr (B_9 _ _) = "b" tagStr (U_9 _ _) = "u" tagStr (S_9 _ _) = "s" tagStr (Strike_9 _ _) = "strike" 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 (Iframe_10 _ _) = "iframe" tagStr (Ins_10 _ _) = "ins" tagStr (Del_10 _ _) = "del" tagStr (Span_10 _ _) = "span" tagStr (Bdo_10 _ _) = "bdo" tagStr (Br_10 _) = "br" tagStr (Em_10 _ _) = "em" tagStr (Strong_10 _ _) = "strong" tagStr (Dfn_10 _ _) = "dfn" tagStr (Code_10 _ _) = "code" tagStr (Samp_10 _ _) = "samp" tagStr (Kbd_10 _ _) = "kbd" tagStr (Var_10 _ _) = "var" tagStr (Cite_10 _ _) = "cite" tagStr (Abbr_10 _ _) = "abbr" tagStr (Acronym_10 _ _) = "acronym" tagStr (Q_10 _ _) = "q" tagStr (Sub_10 _ _) = "sub" tagStr (Sup_10 _ _) = "sup" tagStr (Tt_10 _ _) = "tt" tagStr (I_10 _ _) = "i" tagStr (B_10 _ _) = "b" tagStr (Big_10 _ _) = "big" tagStr (Small_10 _ _) = "small" tagStr (U_10 _ _) = "u" tagStr (S_10 _ _) = "s" tagStr (Strike_10 _ _) = "strike" tagStr (Basefont_10 _) = "basefont" tagStr (Font_10 _ _) = "font" tagStr (Object_10 _ _) = "object" tagStr (Applet_10 _ _) = "applet" tagStr (Img_10 _) = "img" tagStr (Map_10 _ _) = "map" tagStr (Label_10 _ _) = "label" tagStr (Input_10 _) = "input" tagStr (Select_10 _ _) = "select" tagStr (Textarea_10 _ _) = "textarea" tagStr (Button_10 _ _) = "button" tagStr (PCDATA_10 _ _) = "PCDATA" instance TagStr Ent11 where tagStr (Script_11 _ _) = "script" tagStr (Noscript_11 _ _) = "noscript" tagStr (Iframe_11 _ _) = "iframe" 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 (Menu_11 _ _) = "menu" tagStr (Dir_11 _ _) = "dir" tagStr (Dl_11 _ _) = "dl" tagStr (Address_11 _ _) = "address" tagStr (Hr_11 _) = "hr" tagStr (Pre_11 _ _) = "pre" tagStr (Blockquote_11 _ _) = "blockquote" tagStr (Center_11 _ _) = "center" 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 (U_11 _ _) = "u" tagStr (S_11 _ _) = "s" tagStr (Strike_11 _ _) = "strike" tagStr (Basefont_11 _) = "basefont" tagStr (Font_11 _ _) = "font" tagStr (Object_11 _ _) = "object" tagStr (Applet_11 _ _) = "applet" tagStr (Img_11 _) = "img" tagStr (Map_11 _ _) = "map" tagStr (Form_11 _ _) = "form" 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 (Isindex_11 _) = "isindex" tagStr (Table_11 _ _) = "table" tagStr (PCDATA_11 _ _) = "PCDATA" instance TagStr Ent12 where tagStr (Script_12 _ _) = "script" tagStr (Iframe_12 _ _) = "iframe" tagStr (P_12 _ _) = "p" 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 (U_12 _ _) = "u" tagStr (S_12 _ _) = "s" tagStr (Strike_12 _ _) = "strike" tagStr (Basefont_12 _) = "basefont" tagStr (Font_12 _ _) = "font" tagStr (Object_12 _ _) = "object" tagStr (Applet_12 _ _) = "applet" 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 (Button_12 _ _) = "button" tagStr (PCDATA_12 _ _) = "PCDATA" instance TagStr Ent13 where tagStr (Script_13 _ _) = "script" tagStr (Ins_13 _ _) = "ins" tagStr (Del_13 _ _) = "del" tagStr (Span_13 _ _) = "span" tagStr (Bdo_13 _ _) = "bdo" tagStr (Br_13 _) = "br" tagStr (Em_13 _ _) = "em" tagStr (Strong_13 _ _) = "strong" tagStr (Dfn_13 _ _) = "dfn" tagStr (Code_13 _ _) = "code" tagStr (Samp_13 _ _) = "samp" tagStr (Kbd_13 _ _) = "kbd" tagStr (Var_13 _ _) = "var" tagStr (Cite_13 _ _) = "cite" tagStr (Abbr_13 _ _) = "abbr" tagStr (Acronym_13 _ _) = "acronym" tagStr (Q_13 _ _) = "q" tagStr (Tt_13 _ _) = "tt" tagStr (I_13 _ _) = "i" tagStr (B_13 _ _) = "b" tagStr (U_13 _ _) = "u" tagStr (S_13 _ _) = "s" tagStr (Strike_13 _ _) = "strike" tagStr (Label_13 _ _) = "label" tagStr (Input_13 _) = "input" tagStr (Select_13 _ _) = "select" tagStr (Textarea_13 _ _) = "textarea" tagStr (Button_13 _ _) = "button" tagStr (PCDATA_13 _ _) = "PCDATA" instance TagStr Ent14 where tagStr (Script_14 _ _) = "script" tagStr (Noscript_14 _ _) = "noscript" tagStr (Iframe_14 _ _) = "iframe" tagStr (Div_14 _ _) = "div" tagStr (P_14 _ _) = "p" tagStr (H1_14 _ _) = "h1" tagStr (H2_14 _ _) = "h2" tagStr (H3_14 _ _) = "h3" tagStr (H4_14 _ _) = "h4" tagStr (H5_14 _ _) = "h5" tagStr (H6_14 _ _) = "h6" tagStr (Ul_14 _ _) = "ul" tagStr (Ol_14 _ _) = "ol" tagStr (Menu_14 _ _) = "menu" tagStr (Dir_14 _ _) = "dir" tagStr (Dl_14 _ _) = "dl" tagStr (Address_14 _ _) = "address" tagStr (Hr_14 _) = "hr" tagStr (Pre_14 _ _) = "pre" tagStr (Blockquote_14 _ _) = "blockquote" tagStr (Center_14 _ _) = "center" tagStr (Ins_14 _ _) = "ins" tagStr (Del_14 _ _) = "del" tagStr (Span_14 _ _) = "span" tagStr (Bdo_14 _ _) = "bdo" tagStr (Br_14 _) = "br" tagStr (Em_14 _ _) = "em" tagStr (Strong_14 _ _) = "strong" tagStr (Dfn_14 _ _) = "dfn" tagStr (Code_14 _ _) = "code" tagStr (Samp_14 _ _) = "samp" tagStr (Kbd_14 _ _) = "kbd" tagStr (Var_14 _ _) = "var" tagStr (Cite_14 _ _) = "cite" tagStr (Abbr_14 _ _) = "abbr" tagStr (Acronym_14 _ _) = "acronym" tagStr (Q_14 _ _) = "q" tagStr (Sub_14 _ _) = "sub" tagStr (Sup_14 _ _) = "sup" tagStr (Tt_14 _ _) = "tt" tagStr (I_14 _ _) = "i" tagStr (B_14 _ _) = "b" tagStr (Big_14 _ _) = "big" tagStr (Small_14 _ _) = "small" tagStr (U_14 _ _) = "u" tagStr (S_14 _ _) = "s" tagStr (Strike_14 _ _) = "strike" tagStr (Basefont_14 _) = "basefont" tagStr (Font_14 _ _) = "font" tagStr (Object_14 _ _) = "object" tagStr (Applet_14 _ _) = "applet" tagStr (Img_14 _) = "img" tagStr (Map_14 _ _) = "map" tagStr (Label_14 _ _) = "label" tagStr (Input_14 _) = "input" tagStr (Select_14 _ _) = "select" tagStr (Textarea_14 _ _) = "textarea" tagStr (Fieldset_14 _ _) = "fieldset" tagStr (Button_14 _ _) = "button" tagStr (Isindex_14 _) = "isindex" tagStr (Table_14 _ _) = "table" tagStr (PCDATA_14 _ _) = "PCDATA" instance TagStr Ent15 where tagStr (Script_15 _ _) = "script" tagStr (Noscript_15 _ _) = "noscript" tagStr (Iframe_15 _ _) = "iframe" tagStr (Div_15 _ _) = "div" tagStr (P_15 _ _) = "p" tagStr (H1_15 _ _) = "h1" tagStr (H2_15 _ _) = "h2" tagStr (H3_15 _ _) = "h3" tagStr (H4_15 _ _) = "h4" tagStr (H5_15 _ _) = "h5" tagStr (H6_15 _ _) = "h6" tagStr (Ul_15 _ _) = "ul" tagStr (Ol_15 _ _) = "ol" tagStr (Menu_15 _ _) = "menu" tagStr (Dir_15 _ _) = "dir" tagStr (Dl_15 _ _) = "dl" tagStr (Address_15 _ _) = "address" tagStr (Hr_15 _) = "hr" tagStr (Pre_15 _ _) = "pre" tagStr (Blockquote_15 _ _) = "blockquote" tagStr (Center_15 _ _) = "center" tagStr (Ins_15 _ _) = "ins" tagStr (Del_15 _ _) = "del" tagStr (Span_15 _ _) = "span" tagStr (Bdo_15 _ _) = "bdo" tagStr (Br_15 _) = "br" tagStr (Em_15 _ _) = "em" tagStr (Strong_15 _ _) = "strong" tagStr (Dfn_15 _ _) = "dfn" tagStr (Code_15 _ _) = "code" tagStr (Samp_15 _ _) = "samp" tagStr (Kbd_15 _ _) = "kbd" tagStr (Var_15 _ _) = "var" tagStr (Cite_15 _ _) = "cite" tagStr (Abbr_15 _ _) = "abbr" tagStr (Acronym_15 _ _) = "acronym" tagStr (Q_15 _ _) = "q" tagStr (Sub_15 _ _) = "sub" tagStr (Sup_15 _ _) = "sup" tagStr (Tt_15 _ _) = "tt" tagStr (I_15 _ _) = "i" tagStr (B_15 _ _) = "b" tagStr (Big_15 _ _) = "big" tagStr (Small_15 _ _) = "small" tagStr (U_15 _ _) = "u" tagStr (S_15 _ _) = "s" tagStr (Strike_15 _ _) = "strike" tagStr (Basefont_15 _) = "basefont" tagStr (Font_15 _ _) = "font" tagStr (Object_15 _ _) = "object" tagStr (Applet_15 _ _) = "applet" tagStr (Img_15 _) = "img" tagStr (Map_15 _ _) = "map" tagStr (Label_15 _ _) = "label" tagStr (Input_15 _) = "input" tagStr (Select_15 _ _) = "select" tagStr (Textarea_15 _ _) = "textarea" tagStr (Fieldset_15 _ _) = "fieldset" tagStr (Legend_15 _ _) = "legend" tagStr (Button_15 _ _) = "button" tagStr (Isindex_15 _) = "isindex" tagStr (Table_15 _ _) = "table" tagStr (PCDATA_15 _ _) = "PCDATA" instance TagStr Ent16 where tagStr (Caption_16 _ _) = "caption" tagStr (Thead_16 _ _) = "thead" tagStr (Tfoot_16 _ _) = "tfoot" tagStr (Tbody_16 _ _) = "tbody" tagStr (Colgroup_16 _ _) = "colgroup" tagStr (Col_16 _) = "col" tagStr (Tr_16 _ _) = "tr" instance TagStr Ent17 where tagStr (Tr_17 _ _) = "tr" instance TagStr Ent18 where tagStr (Col_18 _) = "col" instance TagStr Ent19 where tagStr (Th_19 _ _) = "th" tagStr (Td_19 _ _) = "td" instance TagStr Ent20 where tagStr (Script_20 _ _) = "script" tagStr (Noscript_20 _ _) = "noscript" tagStr (Iframe_20 _ _) = "iframe" tagStr (Div_20 _ _) = "div" tagStr (P_20 _ _) = "p" tagStr (H1_20 _ _) = "h1" tagStr (H2_20 _ _) = "h2" tagStr (H3_20 _ _) = "h3" tagStr (H4_20 _ _) = "h4" tagStr (H5_20 _ _) = "h5" tagStr (H6_20 _ _) = "h6" tagStr (Ul_20 _ _) = "ul" tagStr (Ol_20 _ _) = "ol" tagStr (Menu_20 _ _) = "menu" tagStr (Dir_20 _ _) = "dir" tagStr (Dl_20 _ _) = "dl" tagStr (Address_20 _ _) = "address" tagStr (Hr_20 _) = "hr" tagStr (Pre_20 _ _) = "pre" tagStr (Blockquote_20 _ _) = "blockquote" tagStr (Center_20 _ _) = "center" 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 (U_20 _ _) = "u" tagStr (S_20 _ _) = "s" tagStr (Strike_20 _ _) = "strike" tagStr (Basefont_20 _) = "basefont" tagStr (Font_20 _ _) = "font" tagStr (Object_20 _ _) = "object" tagStr (Applet_20 _ _) = "applet" tagStr (Img_20 _) = "img" tagStr (Map_20 _ _) = "map" tagStr (Form_20 _ _) = "form" tagStr (Label_20 _ _) = "label" tagStr (Input_20 _) = "input" tagStr (Select_20 _ _) = "select" tagStr (Textarea_20 _ _) = "textarea" tagStr (Fieldset_20 _ _) = "fieldset" tagStr (Legend_20 _ _) = "legend" tagStr (Button_20 _ _) = "button" tagStr (Isindex_20 _) = "isindex" tagStr (Table_20 _ _) = "table" tagStr (PCDATA_20 _ _) = "PCDATA" instance TagStr Ent21 where tagStr (Script_21 _ _) = "script" tagStr (Noscript_21 _ _) = "noscript" tagStr (Iframe_21 _ _) = "iframe" 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 (Menu_21 _ _) = "menu" tagStr (Dir_21 _ _) = "dir" tagStr (Dl_21 _ _) = "dl" tagStr (Address_21 _ _) = "address" tagStr (Hr_21 _) = "hr" tagStr (Pre_21 _ _) = "pre" tagStr (Blockquote_21 _ _) = "blockquote" tagStr (Center_21 _ _) = "center" 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 (U_21 _ _) = "u" tagStr (S_21 _ _) = "s" tagStr (Strike_21 _ _) = "strike" tagStr (Basefont_21 _) = "basefont" tagStr (Font_21 _ _) = "font" tagStr (Object_21 _ _) = "object" tagStr (Param_21 _) = "param" tagStr (Applet_21 _ _) = "applet" tagStr (Img_21 _) = "img" tagStr (Map_21 _ _) = "map" tagStr (Form_21 _ _) = "form" tagStr (Label_21 _ _) = "label" tagStr (Input_21 _) = "input" tagStr (Select_21 _ _) = "select" tagStr (Textarea_21 _ _) = "textarea" tagStr (Fieldset_21 _ _) = "fieldset" tagStr (Button_21 _ _) = "button" tagStr (Isindex_21 _) = "isindex" tagStr (Table_21 _ _) = "table" tagStr (PCDATA_21 _ _) = "PCDATA" instance TagStr Ent22 where tagStr (Script_22 _ _) = "script" tagStr (Noscript_22 _ _) = "noscript" tagStr (Div_22 _ _) = "div" tagStr (P_22 _ _) = "p" tagStr (H1_22 _ _) = "h1" tagStr (H2_22 _ _) = "h2" tagStr (H3_22 _ _) = "h3" tagStr (H4_22 _ _) = "h4" tagStr (H5_22 _ _) = "h5" tagStr (H6_22 _ _) = "h6" tagStr (Ul_22 _ _) = "ul" tagStr (Ol_22 _ _) = "ol" tagStr (Menu_22 _ _) = "menu" tagStr (Dir_22 _ _) = "dir" tagStr (Dl_22 _ _) = "dl" tagStr (Address_22 _ _) = "address" tagStr (Hr_22 _) = "hr" tagStr (Pre_22 _ _) = "pre" tagStr (Blockquote_22 _ _) = "blockquote" tagStr (Center_22 _ _) = "center" tagStr (Ins_22 _ _) = "ins" tagStr (Del_22 _ _) = "del" tagStr (Area_22 _) = "area" tagStr (Form_22 _ _) = "form" tagStr (Fieldset_22 _ _) = "fieldset" tagStr (Isindex_22 _) = "isindex" tagStr (Table_22 _ _) = "table" instance TagStr Ent23 where tagStr (Script_23 _ _) = "script" tagStr (Iframe_23 _ _) = "iframe" 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 (U_23 _ _) = "u" tagStr (S_23 _ _) = "s" tagStr (Strike_23 _ _) = "strike" tagStr (Basefont_23 _) = "basefont" tagStr (Font_23 _ _) = "font" tagStr (Object_23 _ _) = "object" tagStr (Applet_23 _ _) = "applet" tagStr (Img_23 _) = "img" tagStr (Map_23 _ _) = "map" tagStr (Input_23 _) = "input" tagStr (Select_23 _ _) = "select" tagStr (Textarea_23 _ _) = "textarea" tagStr (Button_23 _ _) = "button" tagStr (PCDATA_23 _ _) = "PCDATA" instance TagStr Ent24 where tagStr (Script_24 _ _) = "script" tagStr (Noscript_24 _ _) = "noscript" tagStr (Iframe_24 _ _) = "iframe" 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 (Menu_24 _ _) = "menu" tagStr (Dir_24 _ _) = "dir" tagStr (Dl_24 _ _) = "dl" tagStr (Address_24 _ _) = "address" tagStr (Hr_24 _) = "hr" tagStr (Pre_24 _ _) = "pre" tagStr (Blockquote_24 _ _) = "blockquote" tagStr (Center_24 _ _) = "center" 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 (U_24 _ _) = "u" tagStr (S_24 _ _) = "s" tagStr (Strike_24 _ _) = "strike" tagStr (Basefont_24 _) = "basefont" tagStr (Font_24 _ _) = "font" tagStr (Object_24 _ _) = "object" tagStr (Applet_24 _ _) = "applet" tagStr (Img_24 _) = "img" tagStr (Map_24 _ _) = "map" tagStr (Form_24 _ _) = "form" tagStr (Input_24 _) = "input" tagStr (Select_24 _ _) = "select" tagStr (Textarea_24 _ _) = "textarea" tagStr (Fieldset_24 _ _) = "fieldset" tagStr (Button_24 _ _) = "button" tagStr (Isindex_24 _) = "isindex" tagStr (Table_24 _ _) = "table" tagStr (PCDATA_24 _ _) = "PCDATA" instance TagStr Ent25 where tagStr (Script_25 _ _) = "script" tagStr (Iframe_25 _ _) = "iframe" tagStr (P_25 _ _) = "p" 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 (U_25 _ _) = "u" tagStr (S_25 _ _) = "s" tagStr (Strike_25 _ _) = "strike" tagStr (Basefont_25 _) = "basefont" tagStr (Font_25 _ _) = "font" tagStr (Object_25 _ _) = "object" tagStr (Applet_25 _ _) = "applet" tagStr (Img_25 _) = "img" tagStr (Map_25 _ _) = "map" tagStr (Input_25 _) = "input" tagStr (Select_25 _ _) = "select" tagStr (Textarea_25 _ _) = "textarea" tagStr (Button_25 _ _) = "button" tagStr (PCDATA_25 _ _) = "PCDATA" instance TagStr Ent26 where tagStr (Script_26 _ _) = "script" 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 (Tt_26 _ _) = "tt" tagStr (I_26 _ _) = "i" tagStr (B_26 _ _) = "b" tagStr (U_26 _ _) = "u" tagStr (S_26 _ _) = "s" tagStr (Strike_26 _ _) = "strike" tagStr (Input_26 _) = "input" tagStr (Select_26 _ _) = "select" tagStr (Textarea_26 _ _) = "textarea" tagStr (Button_26 _ _) = "button" tagStr (PCDATA_26 _ _) = "PCDATA" instance TagStr Ent27 where tagStr (Script_27 _ _) = "script" tagStr (Noscript_27 _ _) = "noscript" tagStr (Iframe_27 _ _) = "iframe" tagStr (Div_27 _ _) = "div" tagStr (P_27 _ _) = "p" tagStr (H1_27 _ _) = "h1" tagStr (H2_27 _ _) = "h2" tagStr (H3_27 _ _) = "h3" tagStr (H4_27 _ _) = "h4" tagStr (H5_27 _ _) = "h5" tagStr (H6_27 _ _) = "h6" tagStr (Ul_27 _ _) = "ul" tagStr (Ol_27 _ _) = "ol" tagStr (Menu_27 _ _) = "menu" tagStr (Dir_27 _ _) = "dir" tagStr (Dl_27 _ _) = "dl" tagStr (Address_27 _ _) = "address" tagStr (Hr_27 _) = "hr" tagStr (Pre_27 _ _) = "pre" tagStr (Blockquote_27 _ _) = "blockquote" tagStr (Center_27 _ _) = "center" tagStr (Ins_27 _ _) = "ins" tagStr (Del_27 _ _) = "del" tagStr (Span_27 _ _) = "span" tagStr (Bdo_27 _ _) = "bdo" tagStr (Br_27 _) = "br" tagStr (Em_27 _ _) = "em" tagStr (Strong_27 _ _) = "strong" tagStr (Dfn_27 _ _) = "dfn" tagStr (Code_27 _ _) = "code" tagStr (Samp_27 _ _) = "samp" tagStr (Kbd_27 _ _) = "kbd" tagStr (Var_27 _ _) = "var" tagStr (Cite_27 _ _) = "cite" tagStr (Abbr_27 _ _) = "abbr" tagStr (Acronym_27 _ _) = "acronym" tagStr (Q_27 _ _) = "q" tagStr (Sub_27 _ _) = "sub" tagStr (Sup_27 _ _) = "sup" tagStr (Tt_27 _ _) = "tt" tagStr (I_27 _ _) = "i" tagStr (B_27 _ _) = "b" tagStr (Big_27 _ _) = "big" tagStr (Small_27 _ _) = "small" tagStr (U_27 _ _) = "u" tagStr (S_27 _ _) = "s" tagStr (Strike_27 _ _) = "strike" tagStr (Basefont_27 _) = "basefont" tagStr (Font_27 _ _) = "font" tagStr (Object_27 _ _) = "object" tagStr (Applet_27 _ _) = "applet" tagStr (Img_27 _) = "img" tagStr (Map_27 _ _) = "map" tagStr (Input_27 _) = "input" tagStr (Select_27 _ _) = "select" tagStr (Textarea_27 _ _) = "textarea" tagStr (Fieldset_27 _ _) = "fieldset" tagStr (Button_27 _ _) = "button" tagStr (Isindex_27 _) = "isindex" tagStr (Table_27 _ _) = "table" tagStr (PCDATA_27 _ _) = "PCDATA" instance TagStr Ent28 where tagStr (Script_28 _ _) = "script" tagStr (Noscript_28 _ _) = "noscript" tagStr (Iframe_28 _ _) = "iframe" tagStr (Div_28 _ _) = "div" tagStr (P_28 _ _) = "p" tagStr (H1_28 _ _) = "h1" tagStr (H2_28 _ _) = "h2" tagStr (H3_28 _ _) = "h3" tagStr (H4_28 _ _) = "h4" tagStr (H5_28 _ _) = "h5" tagStr (H6_28 _ _) = "h6" tagStr (Ul_28 _ _) = "ul" tagStr (Ol_28 _ _) = "ol" tagStr (Menu_28 _ _) = "menu" tagStr (Dir_28 _ _) = "dir" tagStr (Dl_28 _ _) = "dl" tagStr (Address_28 _ _) = "address" tagStr (Hr_28 _) = "hr" tagStr (Pre_28 _ _) = "pre" tagStr (Blockquote_28 _ _) = "blockquote" tagStr (Center_28 _ _) = "center" tagStr (Ins_28 _ _) = "ins" tagStr (Del_28 _ _) = "del" tagStr (Span_28 _ _) = "span" tagStr (Bdo_28 _ _) = "bdo" tagStr (Br_28 _) = "br" tagStr (Em_28 _ _) = "em" tagStr (Strong_28 _ _) = "strong" tagStr (Dfn_28 _ _) = "dfn" tagStr (Code_28 _ _) = "code" tagStr (Samp_28 _ _) = "samp" tagStr (Kbd_28 _ _) = "kbd" tagStr (Var_28 _ _) = "var" tagStr (Cite_28 _ _) = "cite" tagStr (Abbr_28 _ _) = "abbr" tagStr (Acronym_28 _ _) = "acronym" tagStr (Q_28 _ _) = "q" tagStr (Sub_28 _ _) = "sub" tagStr (Sup_28 _ _) = "sup" tagStr (Tt_28 _ _) = "tt" tagStr (I_28 _ _) = "i" tagStr (B_28 _ _) = "b" tagStr (Big_28 _ _) = "big" tagStr (Small_28 _ _) = "small" tagStr (U_28 _ _) = "u" tagStr (S_28 _ _) = "s" tagStr (Strike_28 _ _) = "strike" tagStr (Basefont_28 _) = "basefont" tagStr (Font_28 _ _) = "font" tagStr (Object_28 _ _) = "object" tagStr (Applet_28 _ _) = "applet" tagStr (Img_28 _) = "img" tagStr (Map_28 _ _) = "map" tagStr (Input_28 _) = "input" tagStr (Select_28 _ _) = "select" tagStr (Textarea_28 _ _) = "textarea" tagStr (Fieldset_28 _ _) = "fieldset" tagStr (Legend_28 _ _) = "legend" tagStr (Button_28 _ _) = "button" tagStr (Isindex_28 _) = "isindex" tagStr (Table_28 _ _) = "table" tagStr (PCDATA_28 _ _) = "PCDATA" instance TagStr Ent29 where tagStr (Script_29 _ _) = "script" tagStr (Noscript_29 _ _) = "noscript" tagStr (Iframe_29 _ _) = "iframe" 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 (Menu_29 _ _) = "menu" tagStr (Dir_29 _ _) = "dir" tagStr (Dl_29 _ _) = "dl" tagStr (Address_29 _ _) = "address" tagStr (Hr_29 _) = "hr" tagStr (Pre_29 _ _) = "pre" tagStr (Blockquote_29 _ _) = "blockquote" tagStr (Center_29 _ _) = "center" 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 (U_29 _ _) = "u" tagStr (S_29 _ _) = "s" tagStr (Strike_29 _ _) = "strike" tagStr (Basefont_29 _) = "basefont" tagStr (Font_29 _ _) = "font" tagStr (Object_29 _ _) = "object" tagStr (Applet_29 _ _) = "applet" tagStr (Img_29 _) = "img" tagStr (Map_29 _ _) = "map" tagStr (Form_29 _ _) = "form" tagStr (Input_29 _) = "input" tagStr (Select_29 _ _) = "select" tagStr (Textarea_29 _ _) = "textarea" tagStr (Fieldset_29 _ _) = "fieldset" tagStr (Legend_29 _ _) = "legend" tagStr (Button_29 _ _) = "button" tagStr (Isindex_29 _) = "isindex" tagStr (Table_29 _ _) = "table" tagStr (PCDATA_29 _ _) = "PCDATA" instance TagStr Ent30 where tagStr (Script_30 _ _) = "script" tagStr (Noscript_30 _ _) = "noscript" tagStr (Iframe_30 _ _) = "iframe" tagStr (Div_30 _ _) = "div" tagStr (P_30 _ _) = "p" tagStr (H1_30 _ _) = "h1" tagStr (H2_30 _ _) = "h2" tagStr (H3_30 _ _) = "h3" tagStr (H4_30 _ _) = "h4" tagStr (H5_30 _ _) = "h5" tagStr (H6_30 _ _) = "h6" tagStr (Ul_30 _ _) = "ul" tagStr (Ol_30 _ _) = "ol" tagStr (Menu_30 _ _) = "menu" tagStr (Dir_30 _ _) = "dir" tagStr (Dl_30 _ _) = "dl" tagStr (Address_30 _ _) = "address" tagStr (Hr_30 _) = "hr" tagStr (Pre_30 _ _) = "pre" tagStr (Blockquote_30 _ _) = "blockquote" tagStr (Center_30 _ _) = "center" tagStr (Ins_30 _ _) = "ins" tagStr (Del_30 _ _) = "del" 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 (U_30 _ _) = "u" tagStr (S_30 _ _) = "s" tagStr (Strike_30 _ _) = "strike" tagStr (Basefont_30 _) = "basefont" tagStr (Font_30 _ _) = "font" tagStr (Object_30 _ _) = "object" tagStr (Param_30 _) = "param" tagStr (Applet_30 _ _) = "applet" tagStr (Img_30 _) = "img" tagStr (Map_30 _ _) = "map" tagStr (Form_30 _ _) = "form" tagStr (Input_30 _) = "input" tagStr (Select_30 _ _) = "select" tagStr (Textarea_30 _ _) = "textarea" tagStr (Fieldset_30 _ _) = "fieldset" tagStr (Button_30 _ _) = "button" tagStr (Isindex_30 _) = "isindex" tagStr (Table_30 _ _) = "table" tagStr (PCDATA_30 _ _) = "PCDATA" instance TagStr Ent31 where tagStr (Optgroup_31 _ _) = "optgroup" tagStr (Option_31 _ _) = "option" instance TagStr Ent32 where tagStr (Option_32 _ _) = "option" instance TagStr Ent33 where tagStr (Script_33 _ _) = "script" tagStr (Noscript_33 _ _) = "noscript" tagStr (Div_33 _ _) = "div" tagStr (P_33 _ _) = "p" tagStr (H1_33 _ _) = "h1" tagStr (H2_33 _ _) = "h2" tagStr (H3_33 _ _) = "h3" tagStr (H4_33 _ _) = "h4" tagStr (H5_33 _ _) = "h5" tagStr (H6_33 _ _) = "h6" tagStr (Ul_33 _ _) = "ul" tagStr (Ol_33 _ _) = "ol" tagStr (Menu_33 _ _) = "menu" tagStr (Dir_33 _ _) = "dir" tagStr (Dl_33 _ _) = "dl" tagStr (Address_33 _ _) = "address" tagStr (Hr_33 _) = "hr" tagStr (Pre_33 _ _) = "pre" tagStr (Blockquote_33 _ _) = "blockquote" tagStr (Center_33 _ _) = "center" tagStr (Ins_33 _ _) = "ins" tagStr (Del_33 _ _) = "del" 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 (U_33 _ _) = "u" tagStr (S_33 _ _) = "s" tagStr (Strike_33 _ _) = "strike" tagStr (Basefont_33 _) = "basefont" tagStr (Font_33 _ _) = "font" tagStr (Object_33 _ _) = "object" tagStr (Applet_33 _ _) = "applet" tagStr (Img_33 _) = "img" tagStr (Map_33 _ _) = "map" tagStr (Table_33 _ _) = "table" tagStr (PCDATA_33 _ _) = "PCDATA" instance TagStr Ent34 where tagStr (Script_34 _ _) = "script" tagStr (Noscript_34 _ _) = "noscript" tagStr (Iframe_34 _ _) = "iframe" 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 (Menu_34 _ _) = "menu" tagStr (Dir_34 _ _) = "dir" tagStr (Dl_34 _ _) = "dl" tagStr (Address_34 _ _) = "address" tagStr (Hr_34 _) = "hr" tagStr (Pre_34 _ _) = "pre" tagStr (Blockquote_34 _ _) = "blockquote" tagStr (Center_34 _ _) = "center" 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 (U_34 _ _) = "u" tagStr (S_34 _ _) = "s" tagStr (Strike_34 _ _) = "strike" tagStr (Basefont_34 _) = "basefont" tagStr (Font_34 _ _) = "font" tagStr (Object_34 _ _) = "object" tagStr (Applet_34 _ _) = "applet" tagStr (Img_34 _) = "img" tagStr (Map_34 _ _) = "map" tagStr (Label_34 _ _) = "label" tagStr (Input_34 _) = "input" tagStr (Select_34 _ _) = "select" tagStr (Textarea_34 _ _) = "textarea" tagStr (Fieldset_34 _ _) = "fieldset" tagStr (Button_34 _ _) = "button" tagStr (Isindex_34 _) = "isindex" tagStr (Table_34 _ _) = "table" tagStr (PCDATA_34 _ _) = "PCDATA" instance TagStr Ent35 where tagStr (Script_35 _ _) = "script" tagStr (Noscript_35 _ _) = "noscript" tagStr (Iframe_35 _ _) = "iframe" 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 (Menu_35 _ _) = "menu" tagStr (Dir_35 _ _) = "dir" tagStr (Dl_35 _ _) = "dl" tagStr (Address_35 _ _) = "address" tagStr (Hr_35 _) = "hr" tagStr (Pre_35 _ _) = "pre" tagStr (Blockquote_35 _ _) = "blockquote" tagStr (Center_35 _ _) = "center" tagStr (Ins_35 _ _) = "ins" tagStr (Del_35 _ _) = "del" 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 (U_35 _ _) = "u" tagStr (S_35 _ _) = "s" tagStr (Strike_35 _ _) = "strike" tagStr (Basefont_35 _) = "basefont" tagStr (Font_35 _ _) = "font" tagStr (Object_35 _ _) = "object" tagStr (Param_35 _) = "param" tagStr (Applet_35 _ _) = "applet" tagStr (Img_35 _) = "img" tagStr (Map_35 _ _) = "map" tagStr (Label_35 _ _) = "label" tagStr (Input_35 _) = "input" tagStr (Select_35 _ _) = "select" tagStr (Textarea_35 _ _) = "textarea" tagStr (Fieldset_35 _ _) = "fieldset" tagStr (Button_35 _ _) = "button" tagStr (Isindex_35 _) = "isindex" 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 (Menu_36 _ _) = "menu" tagStr (Dir_36 _ _) = "dir" tagStr (Dl_36 _ _) = "dl" tagStr (Address_36 _ _) = "address" tagStr (Hr_36 _) = "hr" tagStr (Pre_36 _ _) = "pre" tagStr (Blockquote_36 _ _) = "blockquote" tagStr (Center_36 _ _) = "center" tagStr (Ins_36 _ _) = "ins" tagStr (Del_36 _ _) = "del" tagStr (Area_36 _) = "area" tagStr (Fieldset_36 _ _) = "fieldset" tagStr (Isindex_36 _) = "isindex" tagStr (Table_36 _ _) = "table" instance TagStr Ent37 where tagStr (Script_37 _ _) = "script" tagStr (Noscript_37 _ _) = "noscript" tagStr (Iframe_37 _ _) = "iframe" 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 (Menu_37 _ _) = "menu" tagStr (Dir_37 _ _) = "dir" tagStr (Dl_37 _ _) = "dl" tagStr (Address_37 _ _) = "address" tagStr (Hr_37 _) = "hr" tagStr (Pre_37 _ _) = "pre" tagStr (Blockquote_37 _ _) = "blockquote" tagStr (Center_37 _ _) = "center" tagStr (Ins_37 _ _) = "ins" tagStr (Del_37 _ _) = "del" 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 (U_37 _ _) = "u" tagStr (S_37 _ _) = "s" tagStr (Strike_37 _ _) = "strike" tagStr (Basefont_37 _) = "basefont" tagStr (Font_37 _ _) = "font" tagStr (Object_37 _ _) = "object" tagStr (Param_37 _) = "param" tagStr (Applet_37 _ _) = "applet" tagStr (Img_37 _) = "img" tagStr (Map_37 _ _) = "map" tagStr (Input_37 _) = "input" tagStr (Select_37 _ _) = "select" tagStr (Textarea_37 _ _) = "textarea" tagStr (Fieldset_37 _ _) = "fieldset" tagStr (Button_37 _ _) = "button" tagStr (Isindex_37 _) = "isindex" tagStr (Table_37 _ _) = "table" tagStr (PCDATA_37 _ _) = "PCDATA" instance TagStr Ent38 where tagStr (Script_38 _ _) = "script" tagStr (Noscript_38 _ _) = "noscript" tagStr (Iframe_38 _ _) = "iframe" 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 (Menu_38 _ _) = "menu" tagStr (Dir_38 _ _) = "dir" tagStr (Dl_38 _ _) = "dl" tagStr (Address_38 _ _) = "address" tagStr (Hr_38 _) = "hr" tagStr (Pre_38 _ _) = "pre" tagStr (Blockquote_38 _ _) = "blockquote" tagStr (Center_38 _ _) = "center" 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 (U_38 _ _) = "u" tagStr (S_38 _ _) = "s" tagStr (Strike_38 _ _) = "strike" tagStr (Basefont_38 _) = "basefont" tagStr (Font_38 _ _) = "font" tagStr (Object_38 _ _) = "object" tagStr (Param_38 _) = "param" tagStr (Applet_38 _ _) = "applet" tagStr (Img_38 _) = "img" tagStr (Map_38 _ _) = "map" 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 (Isindex_38 _) = "isindex" tagStr (Table_38 _ _) = "table" tagStr (PCDATA_38 _ _) = "PCDATA" instance TagStr Ent39 where tagStr (Script_39 _ _) = "script" tagStr (Iframe_39 _ _) = "iframe" 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 (U_39 _ _) = "u" tagStr (S_39 _ _) = "s" tagStr (Strike_39 _ _) = "strike" tagStr (Basefont_39 _) = "basefont" tagStr (Font_39 _ _) = "font" tagStr (Object_39 _ _) = "object" tagStr (Applet_39 _ _) = "applet" tagStr (Img_39 _) = "img" tagStr (Map_39 _ _) = "map" 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 (Iframe_40 _ _) = "iframe" 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 (Menu_40 _ _) = "menu" tagStr (Dir_40 _ _) = "dir" tagStr (Dl_40 _ _) = "dl" tagStr (Address_40 _ _) = "address" tagStr (Hr_40 _) = "hr" tagStr (Pre_40 _ _) = "pre" tagStr (Blockquote_40 _ _) = "blockquote" tagStr (Center_40 _ _) = "center" 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 (U_40 _ _) = "u" tagStr (S_40 _ _) = "s" tagStr (Strike_40 _ _) = "strike" tagStr (Basefont_40 _) = "basefont" tagStr (Font_40 _ _) = "font" tagStr (Object_40 _ _) = "object" tagStr (Applet_40 _ _) = "applet" tagStr (Img_40 _) = "img" tagStr (Map_40 _ _) = "map" tagStr (Input_40 _) = "input" tagStr (Select_40 _ _) = "select" tagStr (Textarea_40 _ _) = "textarea" tagStr (Fieldset_40 _ _) = "fieldset" tagStr (Button_40 _ _) = "button" tagStr (Isindex_40 _) = "isindex" tagStr (Table_40 _ _) = "table" tagStr (PCDATA_40 _ _) = "PCDATA" instance TagStr Ent41 where tagStr (Script_41 _ _) = "script" tagStr (Iframe_41 _ _) = "iframe" tagStr (P_41 _ _) = "p" tagStr (Ins_41 _ _) = "ins" tagStr (Del_41 _ _) = "del" tagStr (A_41 _ _) = "a" 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 (U_41 _ _) = "u" tagStr (S_41 _ _) = "s" tagStr (Strike_41 _ _) = "strike" tagStr (Basefont_41 _) = "basefont" tagStr (Font_41 _ _) = "font" tagStr (Object_41 _ _) = "object" tagStr (Applet_41 _ _) = "applet" tagStr (Img_41 _) = "img" tagStr (Map_41 _ _) = "map" tagStr (Input_41 _) = "input" tagStr (Select_41 _ _) = "select" tagStr (Textarea_41 _ _) = "textarea" tagStr (Button_41 _ _) = "button" tagStr (PCDATA_41 _ _) = "PCDATA" instance TagStr Ent42 where tagStr (Script_42 _ _) = "script" tagStr (Ins_42 _ _) = "ins" tagStr (Del_42 _ _) = "del" tagStr (A_42 _ _) = "a" tagStr (Span_42 _ _) = "span" tagStr (Bdo_42 _ _) = "bdo" tagStr (Br_42 _) = "br" tagStr (Em_42 _ _) = "em" tagStr (Strong_42 _ _) = "strong" tagStr (Dfn_42 _ _) = "dfn" tagStr (Code_42 _ _) = "code" tagStr (Samp_42 _ _) = "samp" tagStr (Kbd_42 _ _) = "kbd" tagStr (Var_42 _ _) = "var" tagStr (Cite_42 _ _) = "cite" tagStr (Abbr_42 _ _) = "abbr" tagStr (Acronym_42 _ _) = "acronym" tagStr (Q_42 _ _) = "q" tagStr (Tt_42 _ _) = "tt" tagStr (I_42 _ _) = "i" tagStr (B_42 _ _) = "b" tagStr (U_42 _ _) = "u" tagStr (S_42 _ _) = "s" tagStr (Strike_42 _ _) = "strike" tagStr (Input_42 _) = "input" tagStr (Select_42 _ _) = "select" tagStr (Textarea_42 _ _) = "textarea" tagStr (Button_42 _ _) = "button" tagStr (PCDATA_42 _ _) = "PCDATA" instance TagStr Ent43 where tagStr (Script_43 _ _) = "script" tagStr (Noscript_43 _ _) = "noscript" tagStr (Iframe_43 _ _) = "iframe" 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 (Menu_43 _ _) = "menu" tagStr (Dir_43 _ _) = "dir" tagStr (Dl_43 _ _) = "dl" tagStr (Address_43 _ _) = "address" tagStr (Hr_43 _) = "hr" tagStr (Pre_43 _ _) = "pre" tagStr (Blockquote_43 _ _) = "blockquote" tagStr (Center_43 _ _) = "center" tagStr (Ins_43 _ _) = "ins" tagStr (Del_43 _ _) = "del" tagStr (A_43 _ _) = "a" 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 (U_43 _ _) = "u" tagStr (S_43 _ _) = "s" tagStr (Strike_43 _ _) = "strike" tagStr (Basefont_43 _) = "basefont" tagStr (Font_43 _ _) = "font" tagStr (Object_43 _ _) = "object" tagStr (Applet_43 _ _) = "applet" 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 (Legend_43 _ _) = "legend" tagStr (Button_43 _ _) = "button" tagStr (Isindex_43 _) = "isindex" tagStr (Table_43 _ _) = "table" tagStr (PCDATA_43 _ _) = "PCDATA" instance TagStr Ent44 where tagStr (Script_44 _ _) = "script" tagStr (Noscript_44 _ _) = "noscript" tagStr (Iframe_44 _ _) = "iframe" 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 (Menu_44 _ _) = "menu" tagStr (Dir_44 _ _) = "dir" tagStr (Dl_44 _ _) = "dl" tagStr (Address_44 _ _) = "address" tagStr (Hr_44 _) = "hr" tagStr (Pre_44 _ _) = "pre" tagStr (Blockquote_44 _ _) = "blockquote" tagStr (Center_44 _ _) = "center" 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 (U_44 _ _) = "u" tagStr (S_44 _ _) = "s" tagStr (Strike_44 _ _) = "strike" tagStr (Basefont_44 _) = "basefont" tagStr (Font_44 _ _) = "font" tagStr (Object_44 _ _) = "object" tagStr (Param_44 _) = "param" tagStr (Applet_44 _ _) = "applet" tagStr (Img_44 _) = "img" tagStr (Map_44 _ _) = "map" tagStr (Input_44 _) = "input" tagStr (Select_44 _ _) = "select" tagStr (Textarea_44 _ _) = "textarea" tagStr (Fieldset_44 _ _) = "fieldset" tagStr (Button_44 _ _) = "button" tagStr (Isindex_44 _) = "isindex" tagStr (Table_44 _ _) = "table" tagStr (PCDATA_44 _ _) = "PCDATA" instance TagStr Ent45 where tagStr (Script_45 _ _) = "script" tagStr (Noscript_45 _ _) = "noscript" tagStr (Iframe_45 _ _) = "iframe" 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 (Menu_45 _ _) = "menu" tagStr (Dir_45 _ _) = "dir" tagStr (Dl_45 _ _) = "dl" tagStr (Address_45 _ _) = "address" tagStr (Hr_45 _) = "hr" tagStr (Pre_45 _ _) = "pre" tagStr (Blockquote_45 _ _) = "blockquote" tagStr (Center_45 _ _) = "center" 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 (U_45 _ _) = "u" tagStr (S_45 _ _) = "s" tagStr (Strike_45 _ _) = "strike" tagStr (Basefont_45 _) = "basefont" tagStr (Font_45 _ _) = "font" tagStr (Object_45 _ _) = "object" tagStr (Applet_45 _ _) = "applet" tagStr (Img_45 _) = "img" tagStr (Map_45 _ _) = "map" tagStr (Label_45 _ _) = "label" tagStr (Input_45 _) = "input" tagStr (Select_45 _ _) = "select" tagStr (Textarea_45 _ _) = "textarea" tagStr (Fieldset_45 _ _) = "fieldset" tagStr (Legend_45 _ _) = "legend" tagStr (Button_45 _ _) = "button" tagStr (Isindex_45 _) = "isindex" tagStr (Table_45 _ _) = "table" tagStr (PCDATA_45 _ _) = "PCDATA" instance TagStr Ent46 where tagStr (Script_46 _ _) = "script" tagStr (Noscript_46 _ _) = "noscript" tagStr (Iframe_46 _ _) = "iframe" 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 (Menu_46 _ _) = "menu" tagStr (Dir_46 _ _) = "dir" tagStr (Dl_46 _ _) = "dl" tagStr (Address_46 _ _) = "address" tagStr (Hr_46 _) = "hr" tagStr (Pre_46 _ _) = "pre" tagStr (Blockquote_46 _ _) = "blockquote" tagStr (Center_46 _ _) = "center" 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 (U_46 _ _) = "u" tagStr (S_46 _ _) = "s" tagStr (Strike_46 _ _) = "strike" tagStr (Basefont_46 _) = "basefont" tagStr (Font_46 _ _) = "font" tagStr (Object_46 _ _) = "object" tagStr (Applet_46 _ _) = "applet" tagStr (Img_46 _) = "img" tagStr (Map_46 _ _) = "map" tagStr (Form_46 _ _) = "form" tagStr (Input_46 _) = "input" tagStr (Select_46 _ _) = "select" tagStr (Textarea_46 _ _) = "textarea" tagStr (Fieldset_46 _ _) = "fieldset" tagStr (Button_46 _ _) = "button" tagStr (Isindex_46 _) = "isindex" tagStr (Table_46 _ _) = "table" tagStr (PCDATA_46 _ _) = "PCDATA" instance TagStr Ent47 where tagStr (Script_47 _ _) = "script" tagStr (Noscript_47 _ _) = "noscript" tagStr (Iframe_47 _ _) = "iframe" 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 (Menu_47 _ _) = "menu" tagStr (Dir_47 _ _) = "dir" tagStr (Dl_47 _ _) = "dl" tagStr (Address_47 _ _) = "address" tagStr (Hr_47 _) = "hr" tagStr (Pre_47 _ _) = "pre" tagStr (Blockquote_47 _ _) = "blockquote" tagStr (Center_47 _ _) = "center" 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 (U_47 _ _) = "u" tagStr (S_47 _ _) = "s" tagStr (Strike_47 _ _) = "strike" tagStr (Basefont_47 _) = "basefont" tagStr (Font_47 _ _) = "font" tagStr (Object_47 _ _) = "object" tagStr (Applet_47 _ _) = "applet" tagStr (Img_47 _) = "img" tagStr (Map_47 _ _) = "map" tagStr (Form_47 _ _) = "form" 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 (Isindex_47 _) = "isindex" tagStr (Table_47 _ _) = "table" tagStr (PCDATA_47 _ _) = "PCDATA" instance TagStr Ent48 where tagStr (Script_48 _ _) = "script" tagStr (Noscript_48 _ _) = "noscript" tagStr (Iframe_48 _ _) = "iframe" tagStr (Div_48 _ _) = "div" tagStr (P_48 _ _) = "p" tagStr (H1_48 _ _) = "h1" tagStr (H2_48 _ _) = "h2" tagStr (H3_48 _ _) = "h3" tagStr (H4_48 _ _) = "h4" tagStr (H5_48 _ _) = "h5" tagStr (H6_48 _ _) = "h6" tagStr (Ul_48 _ _) = "ul" tagStr (Ol_48 _ _) = "ol" tagStr (Menu_48 _ _) = "menu" tagStr (Dir_48 _ _) = "dir" tagStr (Dl_48 _ _) = "dl" tagStr (Address_48 _ _) = "address" tagStr (Hr_48 _) = "hr" tagStr (Pre_48 _ _) = "pre" tagStr (Blockquote_48 _ _) = "blockquote" tagStr (Center_48 _ _) = "center" tagStr (Ins_48 _ _) = "ins" tagStr (Del_48 _ _) = "del" tagStr (A_48 _ _) = "a" tagStr (Span_48 _ _) = "span" tagStr (Bdo_48 _ _) = "bdo" tagStr (Br_48 _) = "br" tagStr (Em_48 _ _) = "em" tagStr (Strong_48 _ _) = "strong" tagStr (Dfn_48 _ _) = "dfn" tagStr (Code_48 _ _) = "code" tagStr (Samp_48 _ _) = "samp" tagStr (Kbd_48 _ _) = "kbd" tagStr (Var_48 _ _) = "var" tagStr (Cite_48 _ _) = "cite" tagStr (Abbr_48 _ _) = "abbr" tagStr (Acronym_48 _ _) = "acronym" tagStr (Q_48 _ _) = "q" tagStr (Sub_48 _ _) = "sub" tagStr (Sup_48 _ _) = "sup" tagStr (Tt_48 _ _) = "tt" tagStr (I_48 _ _) = "i" tagStr (B_48 _ _) = "b" tagStr (Big_48 _ _) = "big" tagStr (Small_48 _ _) = "small" tagStr (U_48 _ _) = "u" tagStr (S_48 _ _) = "s" tagStr (Strike_48 _ _) = "strike" tagStr (Basefont_48 _) = "basefont" tagStr (Font_48 _ _) = "font" tagStr (Object_48 _ _) = "object" tagStr (Param_48 _) = "param" tagStr (Applet_48 _ _) = "applet" tagStr (Img_48 _) = "img" tagStr (Map_48 _ _) = "map" tagStr (Form_48 _ _) = "form" tagStr (Input_48 _) = "input" tagStr (Select_48 _ _) = "select" tagStr (Textarea_48 _ _) = "textarea" tagStr (Fieldset_48 _ _) = "fieldset" tagStr (Button_48 _ _) = "button" tagStr (Isindex_48 _) = "isindex" tagStr (Table_48 _ _) = "table" tagStr (PCDATA_48 _ _) = "PCDATA" instance TagStr Ent49 where tagStr (Script_49 _ _) = "script" tagStr (Noscript_49 _ _) = "noscript" tagStr (Iframe_49 _ _) = "iframe" tagStr (Div_49 _ _) = "div" tagStr (P_49 _ _) = "p" tagStr (H1_49 _ _) = "h1" tagStr (H2_49 _ _) = "h2" tagStr (H3_49 _ _) = "h3" tagStr (H4_49 _ _) = "h4" tagStr (H5_49 _ _) = "h5" tagStr (H6_49 _ _) = "h6" tagStr (Ul_49 _ _) = "ul" tagStr (Ol_49 _ _) = "ol" tagStr (Menu_49 _ _) = "menu" tagStr (Dir_49 _ _) = "dir" tagStr (Dl_49 _ _) = "dl" tagStr (Address_49 _ _) = "address" tagStr (Hr_49 _) = "hr" tagStr (Pre_49 _ _) = "pre" tagStr (Blockquote_49 _ _) = "blockquote" tagStr (Center_49 _ _) = "center" tagStr (Ins_49 _ _) = "ins" tagStr (Del_49 _ _) = "del" tagStr (A_49 _ _) = "a" tagStr (Span_49 _ _) = "span" tagStr (Bdo_49 _ _) = "bdo" tagStr (Br_49 _) = "br" tagStr (Em_49 _ _) = "em" tagStr (Strong_49 _ _) = "strong" tagStr (Dfn_49 _ _) = "dfn" tagStr (Code_49 _ _) = "code" tagStr (Samp_49 _ _) = "samp" tagStr (Kbd_49 _ _) = "kbd" tagStr (Var_49 _ _) = "var" tagStr (Cite_49 _ _) = "cite" tagStr (Abbr_49 _ _) = "abbr" tagStr (Acronym_49 _ _) = "acronym" tagStr (Q_49 _ _) = "q" tagStr (Sub_49 _ _) = "sub" tagStr (Sup_49 _ _) = "sup" tagStr (Tt_49 _ _) = "tt" tagStr (I_49 _ _) = "i" tagStr (B_49 _ _) = "b" tagStr (Big_49 _ _) = "big" tagStr (Small_49 _ _) = "small" tagStr (U_49 _ _) = "u" tagStr (S_49 _ _) = "s" tagStr (Strike_49 _ _) = "strike" tagStr (Basefont_49 _) = "basefont" tagStr (Font_49 _ _) = "font" tagStr (Object_49 _ _) = "object" tagStr (Applet_49 _ _) = "applet" tagStr (Img_49 _) = "img" tagStr (Map_49 _ _) = "map" tagStr (Form_49 _ _) = "form" tagStr (Label_49 _ _) = "label" tagStr (Input_49 _) = "input" tagStr (Select_49 _ _) = "select" tagStr (Textarea_49 _ _) = "textarea" tagStr (Fieldset_49 _ _) = "fieldset" tagStr (Legend_49 _ _) = "legend" tagStr (Button_49 _ _) = "button" tagStr (Isindex_49 _) = "isindex" tagStr (Table_49 _ _) = "table" tagStr (PCDATA_49 _ _) = "PCDATA" instance TagStr Ent50 where tagStr (Frameset_50 _ _) = "frameset" tagStr (Frame_50 _) = "frame" tagStr (Noframes_50 _ _) = "noframes" instance TagStr Ent51 where tagStr (Body_51 _ _) = "body" 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 (Frameset_0 _ c) = ("frameset",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) tagChildren (Isindex_1 _) = [] 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 (Iframe_3 _ c) = ("iframe",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 (Menu_3 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_3 _ c) = ("dir",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 (Center_3 _ c) = ("center",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 (U_3 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_3 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_3 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_3 _) = [] tagChildren (Font_3 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_3 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_3 _) = [] tagChildren (Applet_3 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) 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 (Isindex_3 _) = [] 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 (Noscript_4 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_4 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_4 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_4 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_4 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_4 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_4 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_4 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_4 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_4 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_4 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_4 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_4 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_4 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_4 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_4 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_4 _) = [] tagChildren (Pre_4 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_4 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_4 _ c) = ("center",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 (A_4 _ c) = ("a",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 (U_4 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_4 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_4 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_4 _) = [] tagChildren (Font_4 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_4 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_4 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_4 _) = [] tagChildren (Map_4 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_4 _ c) = ("form",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 (Fieldset_4 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_4 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_4 _) = [] tagChildren (Table_4 _ c) = ("table",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 (Iframe_5 _ c) = ("iframe",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 (A_5 _ c) = ("a",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 (U_5 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_5 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_5 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_5 _) = [] tagChildren (Font_5 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_5 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_5 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_5 _) = [] tagChildren (Map_5 _ c) = ("map",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 (Button_5 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_5 _ _) = [] instance TagChildren Ent6 where tagChildren (Li_6 _ c) = ("li",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent7 where tagChildren (Dt_7 _ c) = ("dt",map tagStr c):(concatMap tagChildren c) tagChildren (Dd_7 _ c) = ("dd",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent8 where tagChildren (Script_8 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_8 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (P_8 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_8 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_8 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_8 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_8 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_8 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_8 _) = [] tagChildren (Em_8 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_8 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_8 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_8 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_8 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_8 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_8 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_8 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_8 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_8 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_8 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_8 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_8 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_8 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_8 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_8 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_8 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_8 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_8 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_8 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_8 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_8 _) = [] tagChildren (Font_8 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_8 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_8 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_8 _) = [] tagChildren (Map_8 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_8 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_8 _) = [] tagChildren (Select_8 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_8 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_8 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_8 _ _) = [] 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 (A_9 _ c) = ("a",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 (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 (U_9 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_9 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_9 _ c) = ("strike",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 (Iframe_10 _ c) = ("iframe",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 (Span_10 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_10 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_10 _) = [] tagChildren (Em_10 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_10 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_10 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_10 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_10 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_10 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_10 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_10 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_10 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_10 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_10 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_10 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_10 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_10 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_10 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_10 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_10 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_10 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_10 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_10 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_10 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_10 _) = [] tagChildren (Font_10 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_10 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_10 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_10 _) = [] tagChildren (Map_10 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_10 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_10 _) = [] tagChildren (Select_10 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_10 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_10 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_10 _ _) = [] 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 (Iframe_11 _ c) = ("iframe",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 (Menu_11 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_11 _ c) = ("dir",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 (Center_11 _ c) = ("center",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 (U_11 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_11 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_11 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_11 _) = [] tagChildren (Font_11 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_11 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_11 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_11 _) = [] tagChildren (Map_11 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_11 _ c) = ("form",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 (Isindex_11 _) = [] 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 (Iframe_12 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (P_12 _ c) = ("p",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 (U_12 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_12 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_12 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_12 _) = [] tagChildren (Font_12 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_12 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_12 _ c) = ("applet",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 (Button_12 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_12 _ _) = [] instance TagChildren Ent13 where tagChildren (Script_13 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_13 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_13 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_13 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_13 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_13 _) = [] tagChildren (Em_13 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_13 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_13 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_13 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_13 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_13 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_13 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_13 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_13 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_13 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_13 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_13 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_13 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_13 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (U_13 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_13 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_13 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Label_13 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_13 _) = [] tagChildren (Select_13 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_13 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_13 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_13 _ _) = [] instance TagChildren Ent14 where tagChildren (Script_14 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_14 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_14 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_14 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_14 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_14 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_14 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_14 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_14 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_14 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_14 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_14 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_14 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_14 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_14 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_14 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_14 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_14 _) = [] tagChildren (Pre_14 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_14 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_14 _ c) = ("center",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_14 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_14 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_14 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_14 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_14 _) = [] tagChildren (Em_14 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_14 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_14 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_14 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_14 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_14 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_14 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_14 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_14 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_14 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_14 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_14 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_14 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_14 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_14 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_14 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_14 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_14 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_14 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_14 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_14 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_14 _) = [] tagChildren (Font_14 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_14 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_14 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_14 _) = [] tagChildren (Map_14 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_14 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_14 _) = [] tagChildren (Select_14 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_14 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_14 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_14 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_14 _) = [] tagChildren (Table_14 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_14 _ _) = [] instance TagChildren Ent15 where tagChildren (Script_15 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_15 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_15 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_15 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_15 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_15 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_15 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_15 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_15 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_15 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_15 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_15 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_15 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_15 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_15 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_15 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_15 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_15 _) = [] tagChildren (Pre_15 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_15 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_15 _ c) = ("center",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_15 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_15 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_15 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_15 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_15 _) = [] tagChildren (Em_15 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_15 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_15 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_15 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_15 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_15 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_15 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_15 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_15 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_15 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_15 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_15 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_15 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_15 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_15 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_15 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_15 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_15 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_15 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_15 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_15 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_15 _) = [] tagChildren (Font_15 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_15 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_15 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_15 _) = [] tagChildren (Map_15 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_15 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_15 _) = [] tagChildren (Select_15 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_15 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_15 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_15 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_15 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_15 _) = [] tagChildren (Table_15 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_15 _ _) = [] instance TagChildren Ent16 where tagChildren (Caption_16 _ c) = ("caption",map tagStr c):(concatMap tagChildren c) tagChildren (Thead_16 _ c) = ("thead",map tagStr c):(concatMap tagChildren c) tagChildren (Tfoot_16 _ c) = ("tfoot",map tagStr c):(concatMap tagChildren c) tagChildren (Tbody_16 _ c) = ("tbody",map tagStr c):(concatMap tagChildren c) tagChildren (Colgroup_16 _ c) = ("colgroup",map tagStr c):(concatMap tagChildren c) tagChildren (Col_16 _) = [] tagChildren (Tr_16 _ c) = ("tr",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent17 where tagChildren (Tr_17 _ c) = ("tr",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent18 where tagChildren (Col_18 _) = [] instance TagChildren Ent19 where tagChildren (Th_19 _ c) = ("th",map tagStr c):(concatMap tagChildren c) tagChildren (Td_19 _ c) = ("td",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent20 where tagChildren (Script_20 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_20 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_20 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_20 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_20 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_20 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_20 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_20 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_20 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_20 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_20 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_20 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_20 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_20 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_20 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_20 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_20 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_20 _) = [] tagChildren (Pre_20 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_20 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_20 _ c) = ("center",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 (U_20 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_20 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_20 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_20 _) = [] tagChildren (Font_20 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_20 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_20 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_20 _) = [] tagChildren (Map_20 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_20 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_20 _ c) = ("label",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 (Fieldset_20 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_20 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_20 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_20 _) = [] tagChildren (Table_20 _ c) = ("table",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 (Iframe_21 _ c) = ("iframe",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 (Menu_21 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_21 _ c) = ("dir",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 (Center_21 _ c) = ("center",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 (U_21 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_21 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_21 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_21 _) = [] tagChildren (Font_21 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_21 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_21 _) = [] tagChildren (Applet_21 _ c) = ("applet",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 (Label_21 _ c) = ("label",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 (Isindex_21 _) = [] 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 (Noscript_22 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_22 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_22 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_22 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_22 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_22 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_22 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_22 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_22 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_22 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_22 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_22 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_22 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_22 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_22 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_22 _) = [] tagChildren (Pre_22 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_22 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_22 _ c) = ("center",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 (Area_22 _) = [] tagChildren (Form_22 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_22 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_22 _) = [] tagChildren (Table_22 _ c) = ("table",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent23 where tagChildren (Script_23 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_23 _ c) = ("iframe",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 (U_23 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_23 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_23 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_23 _) = [] tagChildren (Font_23 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_23 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_23 _ c) = ("applet",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 (Button_23 _ c) = ("button",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 (Iframe_24 _ c) = ("iframe",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 (Menu_24 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_24 _ c) = ("dir",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 (Center_24 _ c) = ("center",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 (U_24 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_24 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_24 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_24 _) = [] tagChildren (Font_24 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_24 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_24 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_24 _) = [] tagChildren (Map_24 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_24 _ c) = ("form",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 (Button_24 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_24 _) = [] 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 (Iframe_25 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (P_25 _ c) = ("p",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 (U_25 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_25 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_25 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_25 _) = [] tagChildren (Font_25 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_25 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_25 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_25 _) = [] tagChildren (Map_25 _ c) = ("map",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 (Button_25 _ c) = ("button",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 (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 (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 (U_26 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_26 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_26 _ c) = ("strike",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 (Button_26 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_26 _ _) = [] instance TagChildren Ent27 where tagChildren (Script_27 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_27 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_27 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_27 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_27 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_27 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_27 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_27 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_27 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_27 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_27 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_27 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_27 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_27 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_27 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_27 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_27 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_27 _) = [] tagChildren (Pre_27 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_27 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_27 _ c) = ("center",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_27 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_27 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_27 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_27 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_27 _) = [] tagChildren (Em_27 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_27 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_27 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_27 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_27 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_27 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_27 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_27 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_27 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_27 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_27 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_27 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_27 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_27 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_27 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_27 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_27 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_27 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_27 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_27 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_27 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_27 _) = [] tagChildren (Font_27 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_27 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_27 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_27 _) = [] tagChildren (Map_27 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_27 _) = [] tagChildren (Select_27 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_27 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_27 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_27 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_27 _) = [] tagChildren (Table_27 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_27 _ _) = [] instance TagChildren Ent28 where tagChildren (Script_28 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_28 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_28 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_28 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_28 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_28 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_28 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_28 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_28 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_28 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_28 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_28 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_28 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_28 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_28 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_28 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_28 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_28 _) = [] tagChildren (Pre_28 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_28 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_28 _ c) = ("center",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_28 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_28 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (Span_28 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_28 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_28 _) = [] tagChildren (Em_28 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_28 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_28 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_28 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_28 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_28 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_28 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_28 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_28 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_28 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_28 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_28 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_28 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_28 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_28 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_28 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_28 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_28 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_28 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_28 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_28 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_28 _) = [] tagChildren (Font_28 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_28 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_28 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_28 _) = [] tagChildren (Map_28 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Input_28 _) = [] tagChildren (Select_28 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_28 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_28 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_28 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_28 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_28 _) = [] tagChildren (Table_28 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_28 _ _) = [] 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 (Iframe_29 _ c) = ("iframe",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 (Menu_29 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_29 _ c) = ("dir",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 (Center_29 _ c) = ("center",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 (U_29 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_29 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_29 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_29 _) = [] tagChildren (Font_29 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_29 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_29 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_29 _) = [] tagChildren (Map_29 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_29 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_29 _) = [] tagChildren (Select_29 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_29 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_29 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_29 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_29 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_29 _) = [] 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 (Noscript_30 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_30 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_30 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_30 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_30 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_30 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_30 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_30 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_30 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_30 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_30 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_30 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_30 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_30 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_30 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_30 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_30 _) = [] tagChildren (Pre_30 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_30 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_30 _ c) = ("center",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 (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 (U_30 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_30 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_30 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_30 _) = [] tagChildren (Font_30 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_30 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_30 _) = [] tagChildren (Applet_30 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_30 _) = [] tagChildren (Map_30 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_30 _ c) = ("form",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 (Fieldset_30 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_30 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_30 _) = [] tagChildren (Table_30 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_30 _ _) = [] instance TagChildren Ent31 where tagChildren (Optgroup_31 _ c) = ("optgroup",map tagStr c):(concatMap tagChildren c) tagChildren (Option_31 _ c) = ("option",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent32 where tagChildren (Option_32 _ c) = ("option",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent33 where tagChildren (Script_33 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_33 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Div_33 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_33 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_33 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_33 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_33 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_33 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_33 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_33 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_33 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_33 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_33 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_33 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_33 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_33 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_33 _) = [] tagChildren (Pre_33 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_33 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_33 _ c) = ("center",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 (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 (U_33 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_33 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_33 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_33 _) = [] tagChildren (Font_33 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_33 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_33 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_33 _) = [] tagChildren (Map_33 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Table_33 _ c) = ("table",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 (Iframe_34 _ c) = ("iframe",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 (Menu_34 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_34 _ c) = ("dir",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 (Center_34 _ c) = ("center",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 (U_34 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_34 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_34 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_34 _) = [] tagChildren (Font_34 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_34 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_34 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_34 _) = [] tagChildren (Map_34 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_34 _ c) = ("label",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 (Isindex_34 _) = [] 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 (Iframe_35 _ c) = ("iframe",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 (Menu_35 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_35 _ c) = ("dir",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 (Center_35 _ c) = ("center",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 (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 (U_35 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_35 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_35 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_35 _) = [] tagChildren (Font_35 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_35 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_35 _) = [] tagChildren (Applet_35 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_35 _) = [] tagChildren (Map_35 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_35 _ c) = ("label",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 (Button_35 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_35 _) = [] 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 (Menu_36 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_36 _ c) = ("dir",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 (Center_36 _ c) = ("center",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 (Area_36 _) = [] tagChildren (Fieldset_36 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_36 _) = [] tagChildren (Table_36 _ c) = ("table",map tagStr c):(concatMap tagChildren c) 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 (Iframe_37 _ c) = ("iframe",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 (Menu_37 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_37 _ c) = ("dir",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 (Center_37 _ c) = ("center",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 (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 (U_37 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_37 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_37 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_37 _) = [] tagChildren (Font_37 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_37 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_37 _) = [] tagChildren (Applet_37 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_37 _) = [] tagChildren (Map_37 _ c) = ("map",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 (Isindex_37 _) = [] 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 (Iframe_38 _ c) = ("iframe",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 (Menu_38 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_38 _ c) = ("dir",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 (Center_38 _ c) = ("center",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 (U_38 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_38 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_38 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_38 _) = [] tagChildren (Font_38 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_38 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_38 _) = [] tagChildren (Applet_38 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_38 _) = [] tagChildren (Map_38 _ c) = ("map",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 (Isindex_38 _) = [] 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 (Iframe_39 _ c) = ("iframe",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 (U_39 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_39 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_39 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_39 _) = [] tagChildren (Font_39 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_39 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_39 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_39 _) = [] tagChildren (Map_39 _ c) = ("map",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 (Iframe_40 _ c) = ("iframe",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 (Menu_40 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_40 _ c) = ("dir",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 (Center_40 _ c) = ("center",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 (U_40 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_40 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_40 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_40 _) = [] tagChildren (Font_40 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_40 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_40 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_40 _) = [] tagChildren (Map_40 _ c) = ("map",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 (Isindex_40 _) = [] 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 (Iframe_41 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (P_41 _ c) = ("p",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 (A_41 _ c) = ("a",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 (U_41 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_41 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_41 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_41 _) = [] tagChildren (Font_41 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_41 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_41 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_41 _) = [] tagChildren (Map_41 _ c) = ("map",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 (Button_41 _ c) = ("button",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 (Ins_42 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_42 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_42 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_42 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_42 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_42 _) = [] tagChildren (Em_42 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_42 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_42 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_42 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_42 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_42 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_42 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_42 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_42 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_42 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_42 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_42 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_42 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_42 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (U_42 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_42 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_42 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Input_42 _) = [] tagChildren (Select_42 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_42 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Button_42 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_42 _ _) = [] 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 (Iframe_43 _ c) = ("iframe",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 (Menu_43 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_43 _ c) = ("dir",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 (Center_43 _ c) = ("center",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 (A_43 _ c) = ("a",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 (U_43 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_43 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_43 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_43 _) = [] tagChildren (Font_43 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_43 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_43 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) 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 (Legend_43 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_43 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_43 _) = [] 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 (Iframe_44 _ c) = ("iframe",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 (Menu_44 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_44 _ c) = ("dir",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 (Center_44 _ c) = ("center",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 (U_44 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_44 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_44 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_44 _) = [] tagChildren (Font_44 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_44 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_44 _) = [] tagChildren (Applet_44 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_44 _) = [] tagChildren (Map_44 _ c) = ("map",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 (Isindex_44 _) = [] 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 (Iframe_45 _ c) = ("iframe",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 (Menu_45 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_45 _ c) = ("dir",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 (Center_45 _ c) = ("center",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 (U_45 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_45 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_45 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_45 _) = [] tagChildren (Font_45 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_45 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_45 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_45 _) = [] tagChildren (Map_45 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Label_45 _ c) = ("label",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 (Legend_45 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_45 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_45 _) = [] 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 (Iframe_46 _ c) = ("iframe",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 (Menu_46 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_46 _ c) = ("dir",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 (Center_46 _ c) = ("center",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 (U_46 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_46 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_46 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_46 _) = [] tagChildren (Font_46 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_46 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_46 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_46 _) = [] tagChildren (Map_46 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_46 _ c) = ("form",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 (Button_46 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_46 _) = [] 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 (Iframe_47 _ c) = ("iframe",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 (Menu_47 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_47 _ c) = ("dir",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 (Center_47 _ c) = ("center",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 (U_47 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_47 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_47 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_47 _) = [] tagChildren (Font_47 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_47 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_47 _ c) = ("applet",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 (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 (Isindex_47 _) = [] tagChildren (Table_47 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_47 _ _) = [] instance TagChildren Ent48 where tagChildren (Script_48 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_48 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_48 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_48 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_48 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_48 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_48 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_48 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_48 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_48 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_48 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_48 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_48 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_48 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_48 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_48 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_48 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_48 _) = [] tagChildren (Pre_48 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_48 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_48 _ c) = ("center",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_48 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_48 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_48 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_48 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_48 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_48 _) = [] tagChildren (Em_48 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_48 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_48 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_48 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_48 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_48 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_48 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_48 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_48 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_48 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_48 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_48 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_48 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_48 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_48 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_48 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_48 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_48 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_48 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_48 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_48 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_48 _) = [] tagChildren (Font_48 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_48 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Param_48 _) = [] tagChildren (Applet_48 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_48 _) = [] tagChildren (Map_48 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_48 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Input_48 _) = [] tagChildren (Select_48 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_48 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_48 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Button_48 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_48 _) = [] tagChildren (Table_48 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_48 _ _) = [] instance TagChildren Ent49 where tagChildren (Script_49 _ c) = ("script",map tagStr c):(concatMap tagChildren c) tagChildren (Noscript_49 _ c) = ("noscript",map tagStr c):(concatMap tagChildren c) tagChildren (Iframe_49 _ c) = ("iframe",map tagStr c):(concatMap tagChildren c) tagChildren (Div_49 _ c) = ("div",map tagStr c):(concatMap tagChildren c) tagChildren (P_49 _ c) = ("p",map tagStr c):(concatMap tagChildren c) tagChildren (H1_49 _ c) = ("h1",map tagStr c):(concatMap tagChildren c) tagChildren (H2_49 _ c) = ("h2",map tagStr c):(concatMap tagChildren c) tagChildren (H3_49 _ c) = ("h3",map tagStr c):(concatMap tagChildren c) tagChildren (H4_49 _ c) = ("h4",map tagStr c):(concatMap tagChildren c) tagChildren (H5_49 _ c) = ("h5",map tagStr c):(concatMap tagChildren c) tagChildren (H6_49 _ c) = ("h6",map tagStr c):(concatMap tagChildren c) tagChildren (Ul_49 _ c) = ("ul",map tagStr c):(concatMap tagChildren c) tagChildren (Ol_49 _ c) = ("ol",map tagStr c):(concatMap tagChildren c) tagChildren (Menu_49 _ c) = ("menu",map tagStr c):(concatMap tagChildren c) tagChildren (Dir_49 _ c) = ("dir",map tagStr c):(concatMap tagChildren c) tagChildren (Dl_49 _ c) = ("dl",map tagStr c):(concatMap tagChildren c) tagChildren (Address_49 _ c) = ("address",map tagStr c):(concatMap tagChildren c) tagChildren (Hr_49 _) = [] tagChildren (Pre_49 _ c) = ("pre",map tagStr c):(concatMap tagChildren c) tagChildren (Blockquote_49 _ c) = ("blockquote",map tagStr c):(concatMap tagChildren c) tagChildren (Center_49 _ c) = ("center",map tagStr c):(concatMap tagChildren c) tagChildren (Ins_49 _ c) = ("ins",map tagStr c):(concatMap tagChildren c) tagChildren (Del_49 _ c) = ("del",map tagStr c):(concatMap tagChildren c) tagChildren (A_49 _ c) = ("a",map tagStr c):(concatMap tagChildren c) tagChildren (Span_49 _ c) = ("span",map tagStr c):(concatMap tagChildren c) tagChildren (Bdo_49 _ c) = ("bdo",map tagStr c):(concatMap tagChildren c) tagChildren (Br_49 _) = [] tagChildren (Em_49 _ c) = ("em",map tagStr c):(concatMap tagChildren c) tagChildren (Strong_49 _ c) = ("strong",map tagStr c):(concatMap tagChildren c) tagChildren (Dfn_49 _ c) = ("dfn",map tagStr c):(concatMap tagChildren c) tagChildren (Code_49 _ c) = ("code",map tagStr c):(concatMap tagChildren c) tagChildren (Samp_49 _ c) = ("samp",map tagStr c):(concatMap tagChildren c) tagChildren (Kbd_49 _ c) = ("kbd",map tagStr c):(concatMap tagChildren c) tagChildren (Var_49 _ c) = ("var",map tagStr c):(concatMap tagChildren c) tagChildren (Cite_49 _ c) = ("cite",map tagStr c):(concatMap tagChildren c) tagChildren (Abbr_49 _ c) = ("abbr",map tagStr c):(concatMap tagChildren c) tagChildren (Acronym_49 _ c) = ("acronym",map tagStr c):(concatMap tagChildren c) tagChildren (Q_49 _ c) = ("q",map tagStr c):(concatMap tagChildren c) tagChildren (Sub_49 _ c) = ("sub",map tagStr c):(concatMap tagChildren c) tagChildren (Sup_49 _ c) = ("sup",map tagStr c):(concatMap tagChildren c) tagChildren (Tt_49 _ c) = ("tt",map tagStr c):(concatMap tagChildren c) tagChildren (I_49 _ c) = ("i",map tagStr c):(concatMap tagChildren c) tagChildren (B_49 _ c) = ("b",map tagStr c):(concatMap tagChildren c) tagChildren (Big_49 _ c) = ("big",map tagStr c):(concatMap tagChildren c) tagChildren (Small_49 _ c) = ("small",map tagStr c):(concatMap tagChildren c) tagChildren (U_49 _ c) = ("u",map tagStr c):(concatMap tagChildren c) tagChildren (S_49 _ c) = ("s",map tagStr c):(concatMap tagChildren c) tagChildren (Strike_49 _ c) = ("strike",map tagStr c):(concatMap tagChildren c) tagChildren (Basefont_49 _) = [] tagChildren (Font_49 _ c) = ("font",map tagStr c):(concatMap tagChildren c) tagChildren (Object_49 _ c) = ("object",map tagStr c):(concatMap tagChildren c) tagChildren (Applet_49 _ c) = ("applet",map tagStr c):(concatMap tagChildren c) tagChildren (Img_49 _) = [] tagChildren (Map_49 _ c) = ("map",map tagStr c):(concatMap tagChildren c) tagChildren (Form_49 _ c) = ("form",map tagStr c):(concatMap tagChildren c) tagChildren (Label_49 _ c) = ("label",map tagStr c):(concatMap tagChildren c) tagChildren (Input_49 _) = [] tagChildren (Select_49 _ c) = ("select",map tagStr c):(concatMap tagChildren c) tagChildren (Textarea_49 _ c) = ("textarea",map tagStr c):(concatMap tagChildren c) tagChildren (Fieldset_49 _ c) = ("fieldset",map tagStr c):(concatMap tagChildren c) tagChildren (Legend_49 _ c) = ("legend",map tagStr c):(concatMap tagChildren c) tagChildren (Button_49 _ c) = ("button",map tagStr c):(concatMap tagChildren c) tagChildren (Isindex_49 _) = [] tagChildren (Table_49 _ c) = ("table",map tagStr c):(concatMap tagChildren c) tagChildren (PCDATA_49 _ _) = [] instance TagChildren Ent50 where tagChildren (Frameset_50 _ c) = ("frameset",map tagStr c):(concatMap tagChildren c) tagChildren (Frame_50 _) = [] tagChildren (Noframes_50 _ c) = ("noframes",map tagStr c):(concatMap tagChildren c) instance TagChildren Ent51 where tagChildren (Body_51 _ c) = ("body",map tagStr c):(concatMap tagChildren c) allowchildren = [("html","^((head)(frameset))$","(head,frameset)"),("head","^(((script)|(style)|(meta)|(link)|(object)|(isindex))*(((title)((script)|(style)|(meta)|(link)|(object)|(isindex))*((base)((script)|(style)|(meta)|(link)|(object)|(isindex))*)?)|((base)((script)|(style)|(meta)|(link)|(object)|(isindex))*((title)((script)|(style)|(meta)|(link)|(object)|(isindex))*))))$","((script|style|meta|link|object|isindex)*,((title,(script|style|meta|link|object|isindex)*,(base,(script|style|meta|link|object|isindex)*)?)|(base,(script|style|meta|link|object|isindex)*,(title,(script|style|meta|link|object|isindex)*))))"),("title","^(PCDATA)$","(#PCDATA)"),("base","^EMPTY$","EMPTY"),("meta","^EMPTY$","EMPTY"),("link","^EMPTY$","EMPTY"),("style","^(PCDATA)$","(#PCDATA)"),("script","^(PCDATA)$","(#PCDATA)"),("noscript","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("frameset","^((frameset)|(frame)|(noframes))*$","(frameset|frame|noframes)*"),("frame","^EMPTY$","EMPTY"),("iframe","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("noframes","^((body))$","(body)"),("body","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("div","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)+"),("menu","^((li))+$","(li)+"),("dir","^((li))+$","(li)+"),("li","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script)|(p))*$","(#PCDATA|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script|p)*"),("hr","^EMPTY$","EMPTY"),("pre","^(PCDATA|(a)|(br)|(span)|(bdo)|(tt)|(i)|(b)|(u)|(s)|(strike)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*$","(#PCDATA|a|br|span|bdo|tt|i|b|u|s|strike|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|input|select|textarea|label|button|ins|del|script)*"),("blockquote","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("center","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("ins","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("u","^(PCDATA|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("s","^(PCDATA|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("strike","^(PCDATA|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("basefont","^EMPTY$","EMPTY"),("font","^(PCDATA|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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"),("applet","^(PCDATA|(param)|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("img","^EMPTY$","EMPTY"),("map","^(((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))+|(area)+)$","((p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|noscript|ins|del|script)+|area+)"),("area","^EMPTY$","EMPTY"),("form","^(PCDATA|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("label","^(PCDATA|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(table)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|table|br|span|bdo|object|applet|img|map|tt|i|b|u|s|strike|big|small|font|basefont|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|noscript|ins|del|script)*"),("isindex","^EMPTY$","EMPTY"),("table","^((caption)?((col)*|(colgroup)*)(thead)?(tfoot)?((tbody)+|(tr)+))$","(caption?,(col*|colgroup*),thead?,tfoot?,(tbody+|tr+))"),("caption","^(PCDATA|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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)|(menu)|(dir)|(pre)|(hr)|(blockquote)|(address)|(center)|(isindex)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(object)|(applet)|(img)|(map)|(iframe)|(tt)|(i)|(b)|(u)|(s)|(strike)|(big)|(small)|(font)|(basefont)|(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|menu|dir|pre|hr|blockquote|address|center|isindex|fieldset|table|form|a|br|span|bdo|object|applet|img|map|iframe|tt|i|b|u|s|strike|big|small|font|basefont|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",4),("link",6),("style",7),("script",9),("noscript",10),("frameset",11),("frame",12),("iframe",13),("noframes",10),("body",14),("div",15),("p",15),("h1",15),("h2",15),("h3",15),("h4",15),("h5",15),("h6",15),("ul",16),("ol",17),("menu",18),("dir",18),("li",19),("dl",18),("dt",10),("dd",10),("address",10),("hr",20),("pre",21),("blockquote",22),("center",10),("ins",23),("del",23),("a",24),("span",10),("bdo",10),("br",27),("em",10),("strong",10),("dfn",10),("code",10),("samp",10),("kbd",10),("var",10),("cite",10),("abbr",10),("acronym",10),("q",22),("sub",10),("sup",10),("tt",10),("i",10),("b",10),("big",10),("small",10),("u",10),("s",10),("strike",10),("basefont",28),("font",30),("object",31),("param",32),("applet",34),("img",37),("map",40),("area",42),("form",43),("label",45),("input",46),("select",47),("optgroup",48),("option",50),("textarea",51),("fieldset",10),("legend",54),("button",55),("isindex",56),("table",57),("caption",15),("thead",58),("tfoot",58),("tbody",58),("colgroup",59),("col",59),("tr",60),("th",61),("td",61),("pcdata",-1),("cdata",-1),("none",-1),("",1)] attList = [["lang","dir","id","xmlns"],["lang","dir","id","profile"],["lang","dir","id"],["id","href","target"],["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","target"],["lang","dir","id","type","media","title","space"],["type"],["id","charset","type","language","src","defer","space"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup"],["id","class","style","title","rows","cols","onload","onunload"],["id","class","style","title","longdesc","name","src","frameborder","marginwidth","marginheight","noresize","scrolling"],["id","class","style","title","longdesc","name","src","frameborder","marginwidth","marginheight","scrolling","align","height","width"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","onload","onunload","background","bgcolor","text","link","vlink","alink"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","align"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","type","compact"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","type","compact","start"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","compact"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","type","value"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","align","noshade","size","width"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","width","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","target"],["id","class","style","title","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","lang","dir"],["dir"],["id","class","style","title","clear"],["id","size","color","face"],["size"],["id","class","style","title","lang","dir","size","color","face"],["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","align","border","hspace","vspace"],["id","name","value","valuetype","type"],["name"],["id","class","style","title","codebase","archive","code","object","alt","name","width","height","align","hspace","vspace"],["width"],["height"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","src","alt","name","longdesc","height","width","usemap","ismap","align","border","hspace","vspace"],["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","target"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","action","method","name","enctype","onsubmit","onreset","accept","accept_charset","target"],["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","align"],["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","align"],["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","prompt"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","summary","width","border","frame","rules","cellspacing","cellpadding","align","bgcolor"],["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","align","char","charoff","valign","bgcolor"],["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","nowrap","bgcolor","width","height"]] groups = [[(1,1),(9,50)],[(2,2),(3,99999),(4,99999),(5,99999),(6,2),(7,2),(64,3),(80,99999)],[(91,99999)],[(7,2),(8,4),(11,4),(14,4),(15,5),(16,5),(17,5),(18,5),(19,5),(20,5),(21,5),(22,6),(23,6),(24,6),(25,6),(27,7),(30,8),(31,99999),(32,9),(33,4),(34,4),(35,4),(36,4),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,3),(65,99999),(66,3),(67,99999),(68,22),(70,34),(71,39),(72,99999),(73,31),(76,2),(77,49),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,4),(11,4),(14,4),(15,5),(16,5),(17,5),(18,5),(19,5),(20,5),(21,5),(22,6),(23,6),(24,6),(25,6),(27,7),(30,8),(31,99999),(32,9),(33,4),(34,4),(35,4),(36,4),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,3),(66,3),(67,99999),(68,22),(70,34),(71,39),(72,99999),(73,31),(76,2),(77,49),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(11,4),(35,4),(36,4),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,3),(66,3),(67,99999),(68,22),(71,39),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(26,4)],[(28,5),(29,4)],[(7,2),(11,4),(15,5),(35,4),(36,4),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,3),(66,3),(67,99999),(68,22),(71,39),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(35,4),(36,4),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(54,5),(55,5),(56,5),(59,5),(60,5),(61,5),(71,39),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(11,11),(35,11),(36,11),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,21),(66,21),(67,99999),(68,22),(71,23),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(8,11),(11,11),(14,11),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,11),(34,11),(35,11),(36,11),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,21),(66,21),(67,99999),(68,22),(70,14),(71,23),(72,99999),(73,31),(76,2),(77,20),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(11,11),(15,10),(35,11),(36,11),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,21),(66,21),(67,99999),(68,22),(71,23),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(35,11),(36,11),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(54,10),(55,10),(56,10),(59,10),(60,10),(61,10),(71,23),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(8,14),(11,14),(14,14),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,2),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,14),(34,14),(35,14),(36,14),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,35),(66,35),(67,99999),(68,36),(71,23),(72,99999),(73,31),(76,2),(77,15),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,14),(11,14),(14,14),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,2),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,14),(34,14),(35,14),(36,14),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,35),(66,35),(67,99999),(68,36),(71,23),(72,99999),(73,31),(76,2),(77,15),(78,10),(79,33),(80,99999),(81,16),(91,99999)],[(82,10),(83,17),(84,17),(85,17),(86,18),(87,99999),(88,19)],[(88,19)],[(87,99999)],[(89,14),(90,14)],[(7,2),(8,11),(11,11),(14,11),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,11),(34,11),(35,11),(36,11),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,21),(66,21),(67,99999),(68,22),(70,14),(71,23),(72,99999),(73,31),(76,2),(77,20),(78,10),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,11),(11,11),(14,11),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,11),(34,11),(35,11),(36,11),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,21),(65,99999),(66,21),(67,99999),(68,22),(70,14),(71,23),(72,99999),(73,31),(76,2),(77,20),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,11),(14,11),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,11),(34,11),(35,11),(36,11),(69,99999),(70,14),(77,20),(80,99999),(81,16)],[(7,2),(11,24),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,30),(66,30),(67,99999),(68,22),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(8,24),(11,24),(14,24),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,24),(34,24),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,30),(66,30),(67,99999),(68,22),(70,27),(72,99999),(73,31),(76,2),(77,29),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(11,24),(15,23),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,30),(66,30),(67,99999),(68,22),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(54,23),(55,23),(56,23),(59,23),(60,23),(61,23),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(8,27),(11,27),(14,27),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,27),(34,27),(35,27),(36,27),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,37),(66,37),(67,99999),(68,36),(72,99999),(73,31),(76,2),(77,28),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,27),(11,27),(14,27),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,27),(34,27),(35,27),(36,27),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,37),(66,37),(67,99999),(68,36),(72,99999),(73,31),(76,2),(77,28),(78,23),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,24),(11,24),(14,24),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,24),(34,24),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,30),(66,30),(67,99999),(68,22),(70,27),(72,99999),(73,31),(76,2),(77,29),(78,23),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,24),(11,24),(14,24),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,24),(34,24),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,30),(65,99999),(66,30),(67,99999),(68,22),(70,27),(72,99999),(73,31),(76,2),(77,29),(79,33),(80,99999),(81,16),(91,99999)],[(74,32),(75,2)],[(75,2)],[(7,2),(8,24),(14,24),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,24),(34,24),(35,24),(36,24),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,30),(66,30),(67,99999),(68,22),(81,16),(91,99999)],[(7,2),(8,34),(11,34),(14,34),(15,5),(16,5),(17,5),(18,5),(19,5),(20,5),(21,5),(22,6),(23,6),(24,6),(25,6),(27,7),(30,8),(31,99999),(32,9),(33,34),(34,34),(35,34),(36,34),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,38),(66,38),(67,99999),(68,36),(71,39),(72,99999),(73,31),(76,2),(77,45),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,14),(11,14),(14,14),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,2),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,14),(34,14),(35,14),(36,14),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,10),(47,10),(48,10),(49,10),(50,10),(51,10),(52,10),(53,10),(54,10),(55,10),(56,10),(57,10),(58,10),(59,10),(60,10),(61,10),(62,99999),(63,10),(64,35),(65,99999),(66,35),(67,99999),(68,36),(71,23),(72,99999),(73,31),(76,2),(77,15),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,14),(14,14),(15,10),(16,10),(17,10),(18,10),(19,10),(20,10),(21,10),(22,6),(23,6),(24,2),(25,6),(27,7),(30,12),(31,99999),(32,13),(33,14),(34,14),(35,14),(36,14),(69,99999),(77,15),(80,99999),(81,16)],[(7,2),(8,27),(11,27),(14,27),(15,23),(16,23),(17,23),(18,23),(19,23),(20,23),(21,23),(22,6),(23,6),(24,6),(25,6),(27,7),(30,25),(31,99999),(32,26),(33,27),(34,27),(35,27),(36,27),(38,23),(39,23),(40,99999),(41,23),(42,23),(43,23),(44,23),(45,23),(46,23),(47,23),(48,23),(49,23),(50,23),(51,23),(52,23),(53,23),(54,23),(55,23),(56,23),(57,23),(58,23),(59,23),(60,23),(61,23),(62,99999),(63,23),(64,37),(65,99999),(66,37),(67,99999),(68,36),(72,99999),(73,31),(76,2),(77,28),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,34),(11,34),(14,34),(15,5),(16,5),(17,5),(18,5),(19,5),(20,5),(21,5),(22,6),(23,6),(24,6),(25,6),(27,7),(30,8),(31,99999),(32,9),(33,34),(34,34),(35,34),(36,34),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,38),(65,99999),(66,38),(67,99999),(68,36),(71,39),(72,99999),(73,31),(76,2),(77,45),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(11,40),(35,40),(36,40),(37,23),(38,39),(39,39),(40,99999),(41,39),(42,39),(43,39),(44,39),(45,39),(46,39),(47,39),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,44),(66,44),(67,99999),(68,36),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(8,40),(11,40),(14,40),(15,39),(16,39),(17,39),(18,39),(19,39),(20,39),(21,39),(22,6),(23,6),(24,6),(25,6),(27,7),(30,41),(31,99999),(32,42),(33,40),(34,40),(35,40),(36,40),(37,23),(38,39),(39,39),(40,99999),(41,39),(42,39),(43,39),(44,39),(45,39),(46,39),(47,39),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,44),(66,44),(67,99999),(68,36),(72,99999),(73,31),(76,2),(77,43),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(11,40),(15,39),(35,40),(36,40),(37,23),(38,39),(39,39),(40,99999),(41,39),(42,39),(43,39),(44,39),(45,39),(46,39),(47,39),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,44),(66,44),(67,99999),(68,36),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(35,40),(36,40),(37,23),(38,39),(39,39),(40,99999),(41,39),(42,39),(43,39),(44,39),(45,39),(46,39),(47,39),(48,39),(49,39),(50,39),(51,39),(54,39),(55,39),(56,39),(59,39),(60,39),(61,39),(72,99999),(73,31),(76,2),(79,33),(91,99999)],[(7,2),(8,40),(11,40),(14,40),(15,39),(16,39),(17,39),(18,39),(19,39),(20,39),(21,39),(22,6),(23,6),(24,6),(25,6),(27,7),(30,41),(31,99999),(32,42),(33,40),(34,40),(35,40),(36,40),(37,23),(38,39),(39,39),(40,99999),(41,39),(42,39),(43,39),(44,39),(45,39),(46,39),(47,39),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,44),(66,44),(67,99999),(68,36),(72,99999),(73,31),(76,2),(77,43),(78,39),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,40),(11,40),(14,40),(15,39),(16,39),(17,39),(18,39),(19,39),(20,39),(21,39),(22,6),(23,6),(24,6),(25,6),(27,7),(30,41),(31,99999),(32,42),(33,40),(34,40),(35,40),(36,40),(37,23),(38,39),(39,39),(40,99999),(41,39),(42,39),(43,39),(44,39),(45,39),(46,39),(47,39),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,44),(65,99999),(66,44),(67,99999),(68,36),(72,99999),(73,31),(76,2),(77,43),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,34),(11,34),(14,34),(15,5),(16,5),(17,5),(18,5),(19,5),(20,5),(21,5),(22,6),(23,6),(24,6),(25,6),(27,7),(30,8),(31,99999),(32,9),(33,34),(34,34),(35,34),(36,34),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,38),(66,38),(67,99999),(68,36),(71,39),(72,99999),(73,31),(76,2),(77,45),(78,5),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,46),(11,46),(14,46),(15,39),(16,39),(17,39),(18,39),(19,39),(20,39),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,41),(31,99999),(32,42),(33,46),(34,46),(35,46),(36,46),(37,23),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,39),(47,10),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,48),(66,48),(67,99999),(68,22),(70,40),(72,99999),(73,31),(76,2),(77,47),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,46),(11,46),(14,46),(15,39),(16,39),(17,39),(18,39),(19,39),(20,39),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,41),(31,99999),(32,42),(33,46),(34,46),(35,46),(36,46),(37,23),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,39),(47,10),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,48),(66,48),(67,99999),(68,22),(70,40),(72,99999),(73,31),(76,2),(77,47),(78,39),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,46),(11,46),(14,46),(15,39),(16,39),(17,39),(18,39),(19,39),(20,39),(21,10),(22,6),(23,6),(24,6),(25,6),(27,7),(30,41),(31,99999),(32,42),(33,46),(34,46),(35,46),(36,46),(37,23),(38,10),(39,10),(40,99999),(41,10),(42,10),(43,10),(44,10),(45,10),(46,39),(47,10),(48,39),(49,39),(50,39),(51,39),(52,39),(53,39),(54,39),(55,39),(56,39),(57,39),(58,39),(59,39),(60,39),(61,39),(62,99999),(63,39),(64,48),(65,99999),(66,48),(67,99999),(68,22),(70,40),(72,99999),(73,31),(76,2),(77,47),(79,33),(80,99999),(81,16),(91,99999)],[(7,2),(8,4),(11,4),(14,4),(15,5),(16,5),(17,5),(18,5),(19,5),(20,5),(21,5),(22,6),(23,6),(24,6),(25,6),(27,7),(30,8),(31,99999),(32,9),(33,4),(34,4),(35,4),(36,4),(37,10),(38,5),(39,5),(40,99999),(41,5),(42,5),(43,5),(44,5),(45,5),(46,5),(47,5),(48,5),(49,5),(50,5),(51,5),(52,5),(53,5),(54,5),(55,5),(56,5),(57,5),(58,5),(59,5),(60,5),(61,5),(62,99999),(63,5),(64,3),(66,3),(67,99999),(68,22),(70,34),(71,39),(72,99999),(73,31),(76,2),(77,49),(78,5),(79,33),(80,99999),(81,16),(91,99999)],[(9,50),(10,99999),(12,51)],[(13,4)],[]] -- | '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)