{-# LANGUAGE  MultiParamTypeClasses,  FunctionalDependencies #-}

-- | 
-- Module      : Text.CHXHtml.XHtml1_strict
-- Copyright   : (c) Paul Talaga 2011,
--
-- License     : BSD-style
--
-- Maintainer  : paul@fuzzpault.com
-- Stability   : experimental
-- Portability : portable
--
--  Description : CHXHtml (Compliant Haskell XHtml) produces W3C valid XHTML1 content by building a datastructure based on the DTD.  
--  Nesting and allowed tags are limited at compile time by recursive types.  Required children, child ordering, and required attributes can be reported at runtime by the
--  @pageErrors function.
--
--  To simplify usage, type classes are used to substitute the correct 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 for 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 escaped for safety.
--  For speed the variant @pcdata_bs "Data.ByteString"@ can be used which bypasses escaping.
--  A handful of character entities (",&,<,>,©,®, ,) can also be used wherever pcdata is allowed by using 
--  the functions: @ce_quot@,@ce_amp@,@ce_lt@,@ce_gt@,@ce_copy@,@ce_reg@,@ce_nbsp@,
--
--  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 first attribute will be used if duplicate names exist.
--
--  Rendering to a "String" is done with the 'render' function, or to a "Data.ByteString" via the 'render_bs' function.  Note that "Data.ByteString" is significatly faster than Strings.
--
--  Under the hood we use a myriad of datatypes for tags and attributes whos details have been omitted below for brevity.  To assist in selecting allowed tags and attributes
--  'htmlHelp' is provided which produces allowed children and attributes given a tag's nesting position.  See 'htmlHelp' below for usage.
--
--
module Text.CHXHtml.XHtml1_strict(  
    -- * Validation
 childErrors,pageErrors,
    -- * Tag & Attribute Help
 htmlHelp,
    -- * Rendering
 render, render_bs,    -- * Tags
pcdata, pcdata_bs,s2b, _html, html_,_a ,a_ ,_abbr ,abbr_ ,_acronym ,acronym_ ,_address ,address_ ,_area ,area_ ,_b ,b_ ,_base ,base_ ,_bdo ,bdo_ ,_big ,big_ ,_blockquote ,blockquote_ ,_body ,body_ ,_br ,br_ ,_button ,button_ ,_caption ,caption_ ,_cite ,cite_ ,_code ,code_ ,_col ,col_ ,_colgroup ,colgroup_ ,_dd ,dd_ ,_del ,del_ ,_dfn ,dfn_ ,_div ,div_ ,_dl ,dl_ ,_dt ,dt_ ,_em ,em_ ,_fieldset ,fieldset_ ,_form ,form_ ,_h1 ,h1_ ,_h2 ,h2_ ,_h3 ,h3_ ,_h4 ,h4_ ,_h5 ,h5_ ,_h6 ,h6_ ,_head ,head_ ,_hr ,hr_ ,_i ,i_ ,_img ,img_ ,_input ,input_ ,_ins ,ins_ ,_kbd ,kbd_ ,_label ,label_ ,_legend ,legend_ ,_li ,li_ ,_link ,link_ ,_map ,map_ ,_meta ,meta_ ,_noscript ,noscript_ ,_object ,object_ ,_ol ,ol_ ,_optgroup ,optgroup_ ,_option ,option_ ,_p ,p_ ,_param ,param_ ,_pre ,pre_ ,_q ,q_ ,_samp ,samp_ ,_script ,script_ ,_select ,select_ ,_small ,small_ ,_span ,span_ ,_strong ,strong_ ,_style ,style_ ,_sub ,sub_ ,_sup ,sup_ ,_table ,table_ ,_tbody ,tbody_ ,_td ,td_ ,_textarea ,textarea_ ,_tfoot ,tfoot_ ,_th ,th_ ,_thead ,thead_ ,_title ,title_ ,_tr ,tr_ ,_tt ,tt_ ,_ul ,ul_ ,_var ,var_ ,
    -- * Attributes
http_equiv_att, http_equiv_att_bs,content_att, content_att_bs,nohref_att, onkeydown_att, onkeydown_att_bs,onkeyup_att, onkeyup_att_bs,onreset_att, onreset_att_bs,onmouseup_att, onmouseup_att_bs,scope_att, onmouseover_att, onmouseover_att_bs,align_att, lang_att, lang_att_bs,valign_att, name_att, name_att_bs,charset_att, charset_att_bs,scheme_att, scheme_att_bs,accept_charset_att, accept_charset_att_bs,onmousedown_att, onmousedown_att_bs,rev_att, rev_att_bs,span_att, span_att_bs,title_att, title_att_bs,onclick_att, onclick_att_bs,width_att, width_att_bs,enctype_att, enctype_att_bs,ismap_att, usemap_att, usemap_att_bs,coords_att, coords_att_bs,frame_att, size_att, size_att_bs,onblur_att, onblur_att_bs,datetime_att, datetime_att_bs,dir_att, summary_att, summary_att_bs,method_att, standby_att, standby_att_bs,tabindex_att, tabindex_att_bs,onmousemove_att, onmousemove_att_bs,style_att, style_att_bs,height_att, height_att_bs,codetype_att, codetype_att_bs,char_att, char_att_bs,multiple_att, codebase_att, codebase_att_bs,xmlns_att, xmlns_att_bs,profile_att, profile_att_bs,rel_att, rel_att_bs,onsubmit_att, onsubmit_att_bs,ondblclick_att, ondblclick_att_bs,axis_att, axis_att_bs,cols_att, cols_att_bs,abbr_att, abbr_att_bs,onchange_att, onchange_att_bs,readonly_att, href_att, href_att_bs,media_att, media_att_bs,id_att, id_att_bs,src_att, src_att_bs,value_att, value_att_bs,for_att, for_att_bs,data_att, data_att_bs,hreflang_att, hreflang_att_bs,checked_att, declare_att, onkeypress_att, onkeypress_att_bs,label_att, label_att_bs,class_att, class_att_bs,type_att, type_att_bs,shape_att, accesskey_att, accesskey_att_bs,headers_att, headers_att_bs,disabled_att, rules_att, rows_att, rows_att_bs,onfocus_att, onfocus_att_bs,colspan_att, colspan_att_bs,rowspan_att, rowspan_att_bs,defer_att, cellspacing_att, cellspacing_att_bs,charoff_att, charoff_att_bs,cite_att, cite_att_bs,maxlength_att, maxlength_att_bs,onselect_att, onselect_att_bs,archive_att, archive_att_bs,alt_att, alt_att_bs,accept_att, accept_att_bs,classid_att, classid_att_bs,longdesc_att, longdesc_att_bs,onmouseout_att, onmouseout_att_bs,border_att, border_att_bs,onunload_att, onunload_att_bs,onload_att, onload_att_bs,action_att, action_att_bs,cellpadding_att, cellpadding_att_bs,valuetype_att, selected_att, 
    -- ** Enumerated Attribute Values
ValuetypeEnum(..),RulesEnum(..),ShapeEnum(..),MethodEnum(..),DirEnum(..),FrameEnum(..),ValignEnum(..),AlignEnum(..),ScopeEnum(..),
    -- ** Character Entities (just a few until I can find a more elegant implementation)
ce_quot,ce_amp,ce_lt,ce_gt,ce_copy,ce_reg,ce_nbsp,
  ) where 

import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.UTF8 as U
import qualified Data.ByteString.Char8 as C
import Data.List (nubBy,sort,intersperse,(\\))
import Data.Char
import Text.Regex.XMLSchema.String
-- | '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)
tagList = [("html",0),("head",1),("title",2),("base",3),("meta",5),("link",7),("style",8),("script",10),("noscript",11),("body",12),("div",11),("p",11),("h1",11),("h2",11),("h3",11),("h4",11),("h5",11),("h6",11),("ul",11),("ol",11),("li",11),("dl",11),("dt",11),("dd",11),("address",11),("hr",11),("pre",11),("blockquote",13),("ins",14),("del",14),("a",15),("span",11),("bdo",11),("br",18),("em",11),("strong",11),("dfn",11),("code",11),("samp",11),("kbd",11),("var",11),("cite",11),("abbr",11),("acronym",11),("q",13),("sub",11),("sup",11),("tt",11),("i",11),("b",11),("big",11),("small",11),("object",19),("param",20),("img",21),("map",24),("area",26),("form",27),("label",29),("input",30),("select",31),("optgroup",32),("option",34),("textarea",35),("fieldset",11),("legend",38),("button",39),("table",40),("caption",11),("thead",41),("tfoot",41),("tbody",41),("colgroup",42),("col",42),("tr",41),("th",43),("td",43),("pcdata",-1),("cdata",-1),("none",-1),("",1)]
attList = [["lang","dir","id","xmlns"],["lang","dir","id","profile"],["lang","dir","id"],["href","id"],["href"],["lang","dir","id","http_equiv","name","content","scheme"],["content"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","charset","href","hreflang","type","rel","rev","media"],["lang","dir","id","type","media","title"],["type"],["id","charset","type","src","defer"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","onload","onunload"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","cite"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","cite","datetime"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","charset","type","name","href","hreflang","rel","rev","shape","coords"],["id","class","style","title","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","lang","dir"],["dir"],["id","class","style","title"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","declare","classid","codebase","data","type","codetype","archive","standby","height","width","usemap","name","tabindex"],["id","name","value","valuetype","type"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","src","alt","longdesc","height","width","usemap","ismap"],["src"],["alt"],["lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","id","class","style","title","name"],["id"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","shape","coords","href","nohref","alt"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","action","method","enctype","onsubmit","onreset","accept","accept_charset"],["action"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","for","accesskey","onfocus","onblur"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","type","name","value","checked","disabled","readonly","size","maxlength","src","alt","usemap","onselect","onchange","accept"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","name","size","multiple","disabled","tabindex","onfocus","onblur","onchange"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","disabled","label"],["label"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","selected","disabled","label","value"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","name","rows","cols","disabled","readonly","onselect","onchange"],["rows"],["cols"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","accesskey","tabindex","onfocus","onblur","name","value","type","disabled"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","summary","width","border","frame","rules","cellspacing","cellpadding"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","align","char","charoff","valign"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","span","width","align","char","charoff","valign"],["id","class","style","title","lang","dir","onclick","ondblclick","onmousedown","onmouseup","onmouseover","onmousemove","onmouseout","onkeypress","onkeydown","onkeyup","abbr","axis","headers","scope","rowspan","colspan","align","char","charoff","valign"]]
groups  = [[(1,1),(9,93)],[(2,2),(3,99999),(4,99999),(5,99999),(6,2),(7,2),(52,3)],[(77,99999)],[(7,2),(8,93),(10,94),(11,60),(12,60),(13,60),(14,60),(15,60),(16,60),(17,60),(18,95),(19,95),(21,96),(24,60),(25,99999),(26,97),(27,93),(28,94),(29,94),(30,4),(31,60),(32,60),(33,99999),(34,60),(35,60),(36,60),(37,60),(38,60),(39,60),(40,60),(41,60),(42,60),(43,60),(44,60),(45,60),(46,60),(47,60),(48,60),(49,60),(50,60),(51,60),(52,3),(53,99999),(54,99999),(55,61),(57,98),(58,62),(59,99999),(60,90),(63,2),(64,133),(66,92),(67,134),(77,99999)],[(7,5),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,27),(54,99999),(55,28),(58,29),(59,99999),(60,57),(63,5),(66,59),(77,99999)],[(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,27),(54,99999),(55,28),(57,11),(58,29),(59,99999),(60,57),(63,5),(64,22),(66,59),(67,23),(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(57,11),(64,22),(67,23)],[(20,6)],[(22,4),(23,6)],[(7,5),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(55,28),(58,29),(59,99999),(60,57),(63,5),(66,59),(77,99999)],[(7,101),(8,11),(10,12),(11,13),(12,13),(13,13),(14,13),(15,13),(16,13),(17,13),(18,14),(19,14),(21,15),(24,13),(25,99999),(26,16),(27,11),(28,12),(29,12),(64,17),(67,18)],[(7,101),(8,11),(10,12),(11,13),(12,13),(13,13),(14,13),(15,13),(16,13),(17,13),(18,14),(19,14),(21,15),(24,13),(25,99999),(26,16),(27,11),(28,12),(29,12),(31,13),(32,13),(33,99999),(34,13),(35,13),(36,13),(37,13),(38,13),(39,13),(40,13),(41,13),(42,13),(43,13),(44,13),(45,13),(46,13),(47,13),(48,13),(49,13),(50,13),(51,13),(52,102),(54,99999),(55,103),(58,38),(59,99999),(60,110),(63,101),(64,17),(66,112),(67,18),(77,99999)],[(7,101),(28,12),(29,12),(31,13),(32,13),(33,99999),(34,13),(35,13),(36,13),(37,13),(38,13),(39,13),(40,13),(41,13),(42,13),(43,13),(44,13),(45,13),(46,13),(47,13),(48,13),(49,13),(50,13),(51,13),(52,102),(54,99999),(55,103),(58,38),(59,99999),(60,110),(63,101),(66,112),(77,99999)],[(20,12)],[(22,13),(23,12)],[(7,101),(28,12),(29,12),(31,13),(32,13),(33,99999),(34,13),(35,13),(36,13),(37,13),(38,13),(39,13),(40,13),(41,13),(42,13),(43,13),(44,13),(45,13),(46,13),(47,13),(48,13),(49,13),(50,13),(51,13),(55,103),(58,38),(59,99999),(60,110),(63,101),(66,112),(77,99999)],[(7,101),(8,11),(10,12),(11,13),(12,13),(13,13),(14,13),(15,13),(16,13),(17,13),(18,14),(19,14),(21,15),(24,13),(25,99999),(26,16),(27,11),(28,12),(29,12),(31,13),(32,13),(33,99999),(34,13),(35,13),(36,13),(37,13),(38,13),(39,13),(40,13),(41,13),(42,13),(43,13),(44,13),(45,13),(46,13),(47,13),(48,13),(49,13),(50,13),(51,13),(52,102),(54,99999),(55,103),(58,38),(59,99999),(60,110),(63,101),(64,17),(65,13),(66,112),(67,18),(77,99999)],[(68,13),(69,19),(70,19),(71,19),(72,20),(73,99999),(74,21)],[(74,21)],[(73,99999)],[(75,12),(76,12)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,27),(54,99999),(55,28),(57,11),(58,29),(59,99999),(60,57),(63,5),(64,22),(65,4),(66,59),(67,23),(77,99999)],[(68,4),(69,24),(70,24),(71,24),(72,25),(73,99999),(74,26)],[(74,26)],[(73,99999)],[(75,6),(76,6)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,27),(53,99999),(54,99999),(55,28),(57,11),(58,29),(59,99999),(60,57),(63,5),(64,22),(66,59),(67,23),(77,99999)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(56,99999),(57,11),(64,22),(67,23)],[(7,30),(28,31),(29,31),(31,29),(32,29),(33,99999),(34,29),(35,29),(36,29),(37,29),(38,29),(39,29),(40,29),(41,29),(42,29),(43,29),(44,29),(45,29),(46,29),(47,29),(48,29),(49,29),(50,29),(51,29),(52,52),(54,99999),(55,53),(59,99999),(60,54),(63,30),(66,56),(77,99999)],[(77,99999)],[(7,30),(8,32),(10,31),(11,29),(12,29),(13,29),(14,29),(15,29),(16,29),(17,29),(18,33),(19,33),(21,34),(24,29),(25,99999),(26,35),(27,32),(28,31),(29,31),(31,29),(32,29),(33,99999),(34,29),(35,29),(36,29),(37,29),(38,29),(39,29),(40,29),(41,29),(42,29),(43,29),(44,29),(45,29),(46,29),(47,29),(48,29),(49,29),(50,29),(51,29),(52,52),(54,99999),(55,53),(57,36),(59,99999),(60,54),(63,30),(64,47),(66,56),(67,48),(77,99999)],[(7,30),(8,32),(10,31),(11,29),(12,29),(13,29),(14,29),(15,29),(16,29),(17,29),(18,33),(19,33),(21,34),(24,29),(25,99999),(26,35),(27,32),(28,31),(29,31),(57,36),(64,47),(67,48)],[(20,31)],[(22,29),(23,31)],[(7,30),(28,31),(29,31),(31,29),(32,29),(33,99999),(34,29),(35,29),(36,29),(37,29),(38,29),(39,29),(40,29),(41,29),(42,29),(43,29),(44,29),(45,29),(46,29),(47,29),(48,29),(49,29),(50,29),(51,29),(55,53),(59,99999),(60,54),(63,30),(66,56),(77,99999)],[(7,104),(8,36),(10,37),(11,38),(12,38),(13,38),(14,38),(15,38),(16,38),(17,38),(18,39),(19,39),(21,40),(24,38),(25,99999),(26,41),(27,36),(28,37),(29,37),(64,42),(67,43)],[(7,104),(8,36),(10,37),(11,38),(12,38),(13,38),(14,38),(15,38),(16,38),(17,38),(18,39),(19,39),(21,40),(24,38),(25,99999),(26,41),(27,36),(28,37),(29,37),(31,38),(32,38),(33,99999),(34,38),(35,38),(36,38),(37,38),(38,38),(39,38),(40,38),(41,38),(42,38),(43,38),(44,38),(45,38),(46,38),(47,38),(48,38),(49,38),(50,38),(51,38),(52,105),(54,99999),(55,106),(59,99999),(60,107),(63,104),(64,42),(66,109),(67,43),(77,99999)],[(7,104),(28,37),(29,37),(31,38),(32,38),(33,99999),(34,38),(35,38),(36,38),(37,38),(38,38),(39,38),(40,38),(41,38),(42,38),(43,38),(44,38),(45,38),(46,38),(47,38),(48,38),(49,38),(50,38),(51,38),(52,105),(54,99999),(55,106),(59,99999),(60,107),(63,104),(66,109),(77,99999)],[(20,37)],[(22,38),(23,37)],[(7,104),(28,37),(29,37),(31,38),(32,38),(33,99999),(34,38),(35,38),(36,38),(37,38),(38,38),(39,38),(40,38),(41,38),(42,38),(43,38),(44,38),(45,38),(46,38),(47,38),(48,38),(49,38),(50,38),(51,38),(55,106),(59,99999),(60,107),(63,104),(66,109),(77,99999)],[(7,104),(8,36),(10,37),(11,38),(12,38),(13,38),(14,38),(15,38),(16,38),(17,38),(18,39),(19,39),(21,40),(24,38),(25,99999),(26,41),(27,36),(28,37),(29,37),(31,38),(32,38),(33,99999),(34,38),(35,38),(36,38),(37,38),(38,38),(39,38),(40,38),(41,38),(42,38),(43,38),(44,38),(45,38),(46,38),(47,38),(48,38),(49,38),(50,38),(51,38),(52,105),(54,99999),(55,106),(59,99999),(60,107),(63,104),(64,42),(65,38),(66,109),(67,43),(77,99999)],[(68,38),(69,44),(70,44),(71,44),(72,45),(73,99999),(74,46)],[(74,46)],[(73,99999)],[(75,37),(76,37)],[(7,30),(8,32),(10,31),(11,29),(12,29),(13,29),(14,29),(15,29),(16,29),(17,29),(18,33),(19,33),(21,34),(24,29),(25,99999),(26,35),(27,32),(28,31),(29,31),(31,29),(32,29),(33,99999),(34,29),(35,29),(36,29),(37,29),(38,29),(39,29),(40,29),(41,29),(42,29),(43,29),(44,29),(45,29),(46,29),(47,29),(48,29),(49,29),(50,29),(51,29),(52,52),(54,99999),(55,53),(57,36),(59,99999),(60,54),(63,30),(64,47),(65,29),(66,56),(67,48),(77,99999)],[(68,29),(69,49),(70,49),(71,49),(72,50),(73,99999),(74,51)],[(74,51)],[(73,99999)],[(75,31),(76,31)],[(7,30),(8,32),(10,31),(11,29),(12,29),(13,29),(14,29),(15,29),(16,29),(17,29),(18,33),(19,33),(21,34),(24,29),(25,99999),(26,35),(27,32),(28,31),(29,31),(31,29),(32,29),(33,99999),(34,29),(35,29),(36,29),(37,29),(38,29),(39,29),(40,29),(41,29),(42,29),(43,29),(44,29),(45,29),(46,29),(47,29),(48,29),(49,29),(50,29),(51,29),(52,52),(53,99999),(54,99999),(55,53),(57,36),(59,99999),(60,54),(63,30),(64,47),(66,56),(67,48),(77,99999)],[(7,30),(8,32),(10,31),(11,29),(12,29),(13,29),(14,29),(15,29),(16,29),(17,29),(18,33),(19,33),(21,34),(24,29),(25,99999),(26,35),(27,32),(28,31),(29,31),(56,99999),(57,36),(64,47),(67,48)],[(61,55),(62,30)],[(62,30)],[(7,30),(8,32),(10,31),(11,29),(12,29),(13,29),(14,29),(15,29),(16,29),(17,29),(18,33),(19,33),(21,34),(24,29),(25,99999),(26,35),(27,32),(28,31),(29,31),(31,29),(32,29),(33,99999),(34,29),(35,29),(36,29),(37,29),(38,29),(39,29),(40,29),(41,29),(42,29),(43,29),(44,29),(45,29),(46,29),(47,29),(48,29),(49,29),(50,29),(51,29),(52,52),(54,99999),(55,53),(67,48),(77,99999)],[(61,58),(62,5)],[(62,5)],[(7,5),(8,7),(10,6),(11,4),(12,4),(13,4),(14,4),(15,4),(16,4),(17,4),(18,8),(19,8),(21,9),(24,4),(25,99999),(26,10),(27,7),(28,6),(29,6),(31,4),(32,4),(33,99999),(34,4),(35,4),(36,4),(37,4),(38,4),(39,4),(40,4),(41,4),(42,4),(43,4),(44,4),(45,4),(46,4),(47,4),(48,4),(49,4),(50,4),(51,4),(52,27),(54,99999),(55,28),(67,23),(77,99999)],[(7,2),(28,94),(29,94),(30,4),(31,60),(32,60),(33,99999),(34,60),(35,60),(36,60),(37,60),(38,60),(39,60),(40,60),(41,60),(42,60),(43,60),(44,60),(45,60),(46,60),(47,60),(48,60),(49,60),(50,60),(51,60),(52,3),(54,99999),(55,61),(58,62),(59,99999),(60,90),(63,2),(66,92),(77,99999)],[(7,2),(8,93),(10,94),(11,60),(12,60),(13,60),(14,60),(15,60),(16,60),(17,60),(18,95),(19,95),(21,96),(24,60),(25,99999),(26,97),(27,93),(28,94),(29,94),(56,99999),(57,98),(64,133),(67,134)],[(7,63),(28,64),(29,64),(30,29),(31,62),(32,62),(33,99999),(34,62),(35,62),(36,62),(37,62),(38,62),(39,62),(40,62),(41,62),(42,62),(43,62),(44,62),(45,62),(46,62),(47,62),(48,62),(49,62),(50,62),(51,62),(52,85),(54,99999),(55,86),(59,99999),(60,87),(63,63),(66,89),(77,99999)],[(77,99999)],[(7,63),(8,65),(10,64),(11,62),(12,62),(13,62),(14,62),(15,62),(16,62),(17,62),(18,66),(19,66),(21,67),(24,62),(25,99999),(26,68),(27,65),(28,64),(29,64),(30,29),(31,62),(32,62),(33,99999),(34,62),(35,62),(36,62),(37,62),(38,62),(39,62),(40,62),(41,62),(42,62),(43,62),(44,62),(45,62),(46,62),(47,62),(48,62),(49,62),(50,62),(51,62),(52,85),(54,99999),(55,86),(57,69),(59,99999),(60,87),(63,63),(64,80),(66,89),(67,81),(77,99999)],[(7,63),(8,65),(10,64),(11,62),(12,62),(13,62),(14,62),(15,62),(16,62),(17,62),(18,66),(19,66),(21,67),(24,62),(25,99999),(26,68),(27,65),(28,64),(29,64),(57,69),(64,80),(67,81)],[(20,64)],[(22,62),(23,64)],[(7,63),(28,64),(29,64),(30,29),(31,62),(32,62),(33,99999),(34,62),(35,62),(36,62),(37,62),(38,62),(39,62),(40,62),(41,62),(42,62),(43,62),(44,62),(45,62),(46,62),(47,62),(48,62),(49,62),(50,62),(51,62),(55,86),(59,99999),(60,87),(63,63),(66,89),(77,99999)],[(7,116),(8,69),(10,70),(11,71),(12,71),(13,71),(14,71),(15,71),(16,71),(17,71),(18,72),(19,72),(21,73),(24,71),(25,99999),(26,74),(27,69),(28,70),(29,70),(64,75),(67,76)],[(7,116),(8,69),(10,70),(11,71),(12,71),(13,71),(14,71),(15,71),(16,71),(17,71),(18,72),(19,72),(21,73),(24,71),(25,99999),(26,74),(27,69),(28,70),(29,70),(30,38),(31,71),(32,71),(33,99999),(34,71),(35,71),(36,71),(37,71),(38,71),(39,71),(40,71),(41,71),(42,71),(43,71),(44,71),(45,71),(46,71),(47,71),(48,71),(49,71),(50,71),(51,71),(52,117),(54,99999),(55,118),(59,99999),(60,119),(63,116),(64,75),(66,121),(67,76),(77,99999)],[(7,116),(28,70),(29,70),(30,38),(31,71),(32,71),(33,99999),(34,71),(35,71),(36,71),(37,71),(38,71),(39,71),(40,71),(41,71),(42,71),(43,71),(44,71),(45,71),(46,71),(47,71),(48,71),(49,71),(50,71),(51,71),(52,117),(54,99999),(55,118),(59,99999),(60,119),(63,116),(66,121),(77,99999)],[(20,70)],[(22,71),(23,70)],[(7,116),(28,70),(29,70),(30,38),(31,71),(32,71),(33,99999),(34,71),(35,71),(36,71),(37,71),(38,71),(39,71),(40,71),(41,71),(42,71),(43,71),(44,71),(45,71),(46,71),(47,71),(48,71),(49,71),(50,71),(51,71),(55,118),(59,99999),(60,119),(63,116),(66,121),(77,99999)],[(7,116),(8,69),(10,70),(11,71),(12,71),(13,71),(14,71),(15,71),(16,71),(17,71),(18,72),(19,72),(21,73),(24,71),(25,99999),(26,74),(27,69),(28,70),(29,70),(30,38),(31,71),(32,71),(33,99999),(34,71),(35,71),(36,71),(37,71),(38,71),(39,71),(40,71),(41,71),(42,71),(43,71),(44,71),(45,71),(46,71),(47,71),(48,71),(49,71),(50,71),(51,71),(52,117),(54,99999),(55,118),(59,99999),(60,119),(63,116),(64,75),(65,71),(66,121),(67,76),(77,99999)],[(68,71),(69,77),(70,77),(71,77),(72,78),(73,99999),(74,79)],[(74,79)],[(73,99999)],[(75,70),(76,70)],[(7,63),(8,65),(10,64),(11,62),(12,62),(13,62),(14,62),(15,62),(16,62),(17,62),(18,66),(19,66),(21,67),(24,62),(25,99999),(26,68),(27,65),(28,64),(29,64),(30,29),(31,62),(32,62),(33,99999),(34,62),(35,62),(36,62),(37,62),(38,62),(39,62),(40,62),(41,62),(42,62),(43,62),(44,62),(45,62),(46,62),(47,62),(48,62),(49,62),(50,62),(51,62),(52,85),(54,99999),(55,86),(57,69),(59,99999),(60,87),(63,63),(64,80),(65,62),(66,89),(67,81),(77,99999)],[(68,62),(69,82),(70,82),(71,82),(72,83),(73,99999),(74,84)],[(74,84)],[(73,99999)],[(75,64),(76,64)],[(7,63),(8,65),(10,64),(11,62),(12,62),(13,62),(14,62),(15,62),(16,62),(17,62),(18,66),(19,66),(21,67),(24,62),(25,99999),(26,68),(27,65),(28,64),(29,64),(30,29),(31,62),(32,62),(33,99999),(34,62),(35,62),(36,62),(37,62),(38,62),(39,62),(40,62),(41,62),(42,62),(43,62),(44,62),(45,62),(46,62),(47,62),(48,62),(49,62),(50,62),(51,62),(52,85),(53,99999),(54,99999),(55,86),(57,69),(59,99999),(60,87),(63,63),(64,80),(66,89),(67,81),(77,99999)],[(7,63),(8,65),(10,64),(11,62),(12,62),(13,62),(14,62),(15,62),(16,62),(17,62),(18,66),(19,66),(21,67),(24,62),(25,99999),(26,68),(27,65),(28,64),(29,64),(56,99999),(57,69),(64,80),(67,81)],[(61,88),(62,63)],[(62,63)],[(7,63),(8,65),(10,64),(11,62),(12,62),(13,62),(14,62),(15,62),(16,62),(17,62),(18,66),(19,66),(21,67),(24,62),(25,99999),(26,68),(27,65),(28,64),(29,64),(31,62),(32,62),(33,99999),(34,62),(35,62),(36,62),(37,62),(38,62),(39,62),(40,62),(41,62),(42,62),(43,62),(44,62),(45,62),(46,62),(47,62),(48,62),(49,62),(50,62),(51,62),(52,85),(54,99999),(55,86),(67,81),(77,99999)],[(61,91),(62,2)],[(62,2)],[(7,2),(8,93),(10,94),(11,60),(12,60),(13,60),(14,60),(15,60),(16,60),(17,60),(18,95),(19,95),(21,96),(24,60),(25,99999),(26,97),(27,93),(28,94),(29,94),(31,60),(32,60),(33,99999),(34,60),(35,60),(36,60),(37,60),(38,60),(39,60),(40,60),(41,60),(42,60),(43,60),(44,60),(45,60),(46,60),(47,60),(48,60),(49,60),(50,60),(51,60),(52,3),(54,99999),(55,61),(67,134),(77,99999)],[(7,2),(8,93),(10,94),(11,60),(12,60),(13,60),(14,60),(15,60),(16,60),(17,60),(18,95),(19,95),(21,96),(24,60),(25,99999),(26,97),(27,93),(28,94),(29,94),(57,98),(64,133),(67,134)],[(7,2),(8,93),(10,94),(11,60),(12,60),(13,60),(14,60),(15,60),(16,60),(17,60),(18,95),(19,95),(21,96),(24,60),(25,99999),(26,97),(27,93),(28,94),(29,94),(30,4),(31,60),(32,60),(33,99999),(34,60),(35,60),(36,60),(37,60),(38,60),(39,60),(40,60),(41,60),(42,60),(43,60),(44,60),(45,60),(46,60),(47,60),(48,60),(49,60),(50,60),(51,60),(52,3),(54,99999),(55,61),(57,98),(58,62),(59,99999),(60,90),(63,2),(64,133),(66,92),(67,134),(77,99999)],[(20,94)],[(22,60),(23,94)],[(7,2),(28,94),(29,94),(30,4),(31,60),(32,60),(33,99999),(34,60),(35,60),(36,60),(37,60),(38,60),(39,60),(40,60),(41,60),(42,60),(43,60),(44,60),(45,60),(46,60),(47,60),(48,60),(49,60),(50,60),(51,60),(55,61),(58,62),(59,99999),(60,90),(63,2),(66,92),(77,99999)],[(7,99),(8,98),(10,100),(11,113),(12,113),(13,113),(14,113),(15,113),(16,113),(17,113),(18,125),(19,125),(21,126),(24,113),(25,99999),(26,127),(27,98),(28,100),(29,100),(64,128),(67,129)],[(77,99999)],[(7,99),(8,98),(10,100),(11,113),(12,113),(13,113),(14,113),(15,113),(16,113),(17,113),(18,125),(19,125),(21,126),(24,113),(25,99999),(26,127),(27,98),(28,100),(29,100),(30,13),(31,113),(32,113),(33,99999),(34,113),(35,113),(36,113),(37,113),(38,113),(39,113),(40,113),(41,113),(42,113),(43,113),(44,113),(45,113),(46,113),(47,113),(48,113),(49,113),(50,113),(51,113),(52,114),(54,99999),(55,115),(58,71),(59,99999),(60,122),(63,99),(64,128),(66,124),(67,129),(77,99999)],[(77,99999)],[(7,101),(8,11),(10,12),(11,13),(12,13),(13,13),(14,13),(15,13),(16,13),(17,13),(18,14),(19,14),(21,15),(24,13),(25,99999),(26,16),(27,11),(28,12),(29,12),(31,13),(32,13),(33,99999),(34,13),(35,13),(36,13),(37,13),(38,13),(39,13),(40,13),(41,13),(42,13),(43,13),(44,13),(45,13),(46,13),(47,13),(48,13),(49,13),(50,13),(51,13),(52,102),(53,99999),(54,99999),(55,103),(58,38),(59,99999),(60,110),(63,101),(64,17),(66,112),(67,18),(77,99999)],[(7,101),(8,11),(10,12),(11,13),(12,13),(13,13),(14,13),(15,13),(16,13),(17,13),(18,14),(19,14),(21,15),(24,13),(25,99999),(26,16),(27,11),(28,12),(29,12),(56,99999),(64,17),(67,18)],[(77,99999)],[(7,104),(8,36),(10,37),(11,38),(12,38),(13,38),(14,38),(15,38),(16,38),(17,38),(18,39),(19,39),(21,40),(24,38),(25,99999),(26,41),(27,36),(28,37),(29,37),(31,38),(32,38),(33,99999),(34,38),(35,38),(36,38),(37,38),(38,38),(39,38),(40,38),(41,38),(42,38),(43,38),(44,38),(45,38),(46,38),(47,38),(48,38),(49,38),(50,38),(51,38),(52,105),(53,99999),(54,99999),(55,106),(59,99999),(60,107),(63,104),(64,42),(66,109),(67,43),(77,99999)],[(7,104),(8,36),(10,37),(11,38),(12,38),(13,38),(14,38),(15,38),(16,38),(17,38),(18,39),(19,39),(21,40),(24,38),(25,99999),(26,41),(27,36),(28,37),(29,37),(56,99999),(64,42),(67,43)],[(61,108),(62,104)],[(62,104)],[(7,104),(8,36),(10,37),(11,38),(12,38),(13,38),(14,38),(15,38),(16,38),(17,38),(18,39),(19,39),(21,40),(24,38),(25,99999),(26,41),(27,36),(28,37),(29,37),(31,38),(32,38),(33,99999),(34,38),(35,38),(36,38),(37,38),(38,38),(39,38),(40,38),(41,38),(42,38),(43,38),(44,38),(45,38),(46,38),(47,38),(48,38),(49,38),(50,38),(51,38),(52,105),(54,99999),(55,106),(67,43),(77,99999)],[(61,111),(62,101)],[(62,101)],[(7,101),(8,11),(10,12),(11,13),(12,13),(13,13),(14,13),(15,13),(16,13),(17,13),(18,14),(19,14),(21,15),(24,13),(25,99999),(26,16),(27,11),(28,12),(29,12),(31,13),(32,13),(33,99999),(34,13),(35,13),(36,13),(37,13),(38,13),(39,13),(40,13),(41,13),(42,13),(43,13),(44,13),(45,13),(46,13),(47,13),(48,13),(49,13),(50,13),(51,13),(52,102),(54,99999),(55,103),(67,18),(77,99999)],[(7,99),(28,100),(29,100),(30,13),(31,113),(32,113),(33,99999),(34,113),(35,113),(36,113),(37,113),(38,113),(39,113),(40,113),(41,113),(42,113),(43,113),(44,113),(45,113),(46,113),(47,113),(48,113),(49,113),(50,113),(51,113),(52,114),(54,99999),(55,115),(58,71),(59,99999),(60,122),(63,99),(66,124),(77,99999)],[(7,99),(8,98),(10,100),(11,113),(12,113),(13,113),(14,113),(15,113),(16,113),(17,113),(18,125),(19,125),(21,126),(24,113),(25,99999),(26,127),(27,98),(28,100),(29,100),(30,13),(31,113),(32,113),(33,99999),(34,113),(35,113),(36,113),(37,113),(38,113),(39,113),(40,113),(41,113),(42,113),(43,113),(44,113),(45,113),(46,113),(47,113),(48,113),(49,113),(50,113),(51,113),(52,114),(53,99999),(54,99999),(55,115),(58,71),(59,99999),(60,122),(63,99),(64,128),(66,124),(67,129),(77,99999)],[(7,99),(8,98),(10,100),(11,113),(12,113),(13,113),(14,113),(15,113),(16,113),(17,113),(18,125),(19,125),(21,126),(24,113),(25,99999),(26,127),(27,98),(28,100),(29,100),(56,99999),(64,128),(67,129)],[(77,99999)],[(7,116),(8,69),(10,70),(11,71),(12,71),(13,71),(14,71),(15,71),(16,71),(17,71),(18,72),(19,72),(21,73),(24,71),(25,99999),(26,74),(27,69),(28,70),(29,70),(30,38),(31,71),(32,71),(33,99999),(34,71),(35,71),(36,71),(37,71),(38,71),(39,71),(40,71),(41,71),(42,71),(43,71),(44,71),(45,71),(46,71),(47,71),(48,71),(49,71),(50,71),(51,71),(52,117),(53,99999),(54,99999),(55,118),(59,99999),(60,119),(63,116),(64,75),(66,121),(67,76),(77,99999)],[(7,116),(8,69),(10,70),(11,71),(12,71),(13,71),(14,71),(15,71),(16,71),(17,71),(18,72),(19,72),(21,73),(24,71),(25,99999),(26,74),(27,69),(28,70),(29,70),(56,99999),(64,75),(67,76)],[(61,120),(62,116)],[(62,116)],[(7,116),(8,69),(10,70),(11,71),(12,71),(13,71),(14,71),(15,71),(16,71),(17,71),(18,72),(19,72),(21,73),(24,71),(25,99999),(26,74),(27,69),(28,70),(29,70),(31,71),(32,71),(33,99999),(34,71),(35,71),(36,71),(37,71),(38,71),(39,71),(40,71),(41,71),(42,71),(43,71),(44,71),(45,71),(46,71),(47,71),(48,71),(49,71),(50,71),(51,71),(52,117),(54,99999),(55,118),(67,76),(77,99999)],[(61,123),(62,99)],[(62,99)],[(7,99),(8,98),(10,100),(11,113),(12,113),(13,113),(14,113),(15,113),(16,113),(17,113),(18,125),(19,125),(21,126),(24,113),(25,99999),(26,127),(27,98),(28,100),(29,100),(31,113),(32,113),(33,99999),(34,113),(35,113),(36,113),(37,113),(38,113),(39,113),(40,113),(41,113),(42,113),(43,113),(44,113),(45,113),(46,113),(47,113),(48,113),(49,113),(50,113),(51,113),(52,114),(54,99999),(55,115),(67,129),(77,99999)],[(20,100)],[(22,113),(23,100)],[(7,99),(28,100),(29,100),(30,13),(31,113),(32,113),(33,99999),(34,113),(35,113),(36,113),(37,113),(38,113),(39,113),(40,113),(41,113),(42,113),(43,113),(44,113),(45,113),(46,113),(47,113),(48,113),(49,113),(50,113),(51,113),(55,115),(58,71),(59,99999),(60,122),(63,99),(66,124),(77,99999)],[(7,99),(8,98),(10,100),(11,113),(12,113),(13,113),(14,113),(15,113),(16,113),(17,113),(18,125),(19,125),(21,126),(24,113),(25,99999),(26,127),(27,98),(28,100),(29,100),(30,13),(31,113),(32,113),(33,99999),(34,113),(35,113),(36,113),(37,113),(38,113),(39,113),(40,113),(41,113),(42,113),(43,113),(44,113),(45,113),(46,113),(47,113),(48,113),(49,113),(50,113),(51,113),(52,114),(54,99999),(55,115),(58,71),(59,99999),(60,122),(63,99),(64,128),(65,113),(66,124),(67,129),(77,99999)],[(68,113),(69,130),(70,130),(71,130),(72,131),(73,99999),(74,132)],[(74,132)],[(73,99999)],[(75,100),(76,100)],[(7,2),(8,93),(10,94),(11,60),(12,60),(13,60),(14,60),(15,60),(16,60),(17,60),(18,95),(19,95),(21,96),(24,60),(25,99999),(26,97),(27,93),(28,94),(29,94),(30,4),(31,60),(32,60),(33,99999),(34,60),(35,60),(36,60),(37,60),(38,60),(39,60),(40,60),(41,60),(42,60),(43,60),(44,60),(45,60),(46,60),(47,60),(48,60),(49,60),(50,60),(51,60),(52,3),(54,99999),(55,61),(57,98),(58,62),(59,99999),(60,90),(63,2),(64,133),(65,60),(66,92),(67,134),(77,99999)],[(68,60),(69,135),(70,135),(71,135),(72,136),(73,99999),(74,137)],[(74,137)],[(73,99999)],[(75,94),(76,94)],[]]



-- Bytestring conversion functions
s2b_escape = U.fromString . stringToHtmlString
stringToHtmlString = concatMap fixChar
    where
      fixChar '<' = "&lt;"
      fixChar '>' = "&gt;"
      fixChar '&' = "&amp;"
      fixChar '"' = "&quot;"
      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 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  | Abbr_Att_43 B.ByteString  | Axis_Att_43 B.ByteString  | Headers_Att_43 B.ByteString  | Scope_Att_43 B.ByteString  | Rowspan_Att_43 B.ByteString  | Colspan_Att_43 B.ByteString  | Align_Att_43 B.ByteString  | Char_Att_43 B.ByteString  | Charoff_Att_43 B.ByteString  | Valign_Att_43 B.ByteString 
   deriving (Show)
data Att42 = Id_Att_42 B.ByteString  | Class_Att_42 B.ByteString  | Style_Att_42 B.ByteString  | Title_Att_42 B.ByteString  | Lang_Att_42 B.ByteString  | Dir_Att_42 B.ByteString  | Onclick_Att_42 B.ByteString  | Ondblclick_Att_42 B.ByteString  | Onmousedown_Att_42 B.ByteString  | Onmouseup_Att_42 B.ByteString  | Onmouseover_Att_42 B.ByteString  | Onmousemove_Att_42 B.ByteString  | Onmouseout_Att_42 B.ByteString  | Onkeypress_Att_42 B.ByteString  | Onkeydown_Att_42 B.ByteString  | Onkeyup_Att_42 B.ByteString  | Span_Att_42 B.ByteString  | Width_Att_42 B.ByteString  | Align_Att_42 B.ByteString  | Char_Att_42 B.ByteString  | Charoff_Att_42 B.ByteString  | Valign_Att_42 B.ByteString 
   deriving (Show)
data Att41 = Id_Att_41 B.ByteString  | Class_Att_41 B.ByteString  | Style_Att_41 B.ByteString  | Title_Att_41 B.ByteString  | Lang_Att_41 B.ByteString  | Dir_Att_41 B.ByteString  | Onclick_Att_41 B.ByteString  | Ondblclick_Att_41 B.ByteString  | Onmousedown_Att_41 B.ByteString  | Onmouseup_Att_41 B.ByteString  | Onmouseover_Att_41 B.ByteString  | Onmousemove_Att_41 B.ByteString  | Onmouseout_Att_41 B.ByteString  | Onkeypress_Att_41 B.ByteString  | Onkeydown_Att_41 B.ByteString  | Onkeyup_Att_41 B.ByteString  | Align_Att_41 B.ByteString  | Char_Att_41 B.ByteString  | Charoff_Att_41 B.ByteString  | Valign_Att_41 B.ByteString 
   deriving (Show)
data Att40 = Id_Att_40 B.ByteString  | Class_Att_40 B.ByteString  | Style_Att_40 B.ByteString  | Title_Att_40 B.ByteString  | Lang_Att_40 B.ByteString  | Dir_Att_40 B.ByteString  | Onclick_Att_40 B.ByteString  | Ondblclick_Att_40 B.ByteString  | Onmousedown_Att_40 B.ByteString  | Onmouseup_Att_40 B.ByteString  | Onmouseover_Att_40 B.ByteString  | Onmousemove_Att_40 B.ByteString  | Onmouseout_Att_40 B.ByteString  | Onkeypress_Att_40 B.ByteString  | Onkeydown_Att_40 B.ByteString  | Onkeyup_Att_40 B.ByteString  | Summary_Att_40 B.ByteString  | Width_Att_40 B.ByteString  | Border_Att_40 B.ByteString  | Frame_Att_40 B.ByteString  | Rules_Att_40 B.ByteString  | Cellspacing_Att_40 B.ByteString  | Cellpadding_Att_40 B.ByteString 
   deriving (Show)
data Att39 = Id_Att_39 B.ByteString  | Class_Att_39 B.ByteString  | Style_Att_39 B.ByteString  | Title_Att_39 B.ByteString  | Lang_Att_39 B.ByteString  | Dir_Att_39 B.ByteString  | Onclick_Att_39 B.ByteString  | Ondblclick_Att_39 B.ByteString  | Onmousedown_Att_39 B.ByteString  | Onmouseup_Att_39 B.ByteString  | Onmouseover_Att_39 B.ByteString  | Onmousemove_Att_39 B.ByteString  | Onmouseout_Att_39 B.ByteString  | Onkeypress_Att_39 B.ByteString  | Onkeydown_Att_39 B.ByteString  | Onkeyup_Att_39 B.ByteString  | Accesskey_Att_39 B.ByteString  | Tabindex_Att_39 B.ByteString  | Onfocus_Att_39 B.ByteString  | Onblur_Att_39 B.ByteString  | Name_Att_39 B.ByteString  | Value_Att_39 B.ByteString  | Type_Att_39 B.ByteString  | Disabled_Att_39 B.ByteString 
   deriving (Show)
data Att38 = Id_Att_38 B.ByteString  | Class_Att_38 B.ByteString  | Style_Att_38 B.ByteString  | Title_Att_38 B.ByteString  | Lang_Att_38 B.ByteString  | Dir_Att_38 B.ByteString  | Onclick_Att_38 B.ByteString  | Ondblclick_Att_38 B.ByteString  | Onmousedown_Att_38 B.ByteString  | Onmouseup_Att_38 B.ByteString  | Onmouseover_Att_38 B.ByteString  | Onmousemove_Att_38 B.ByteString  | Onmouseout_Att_38 B.ByteString  | Onkeypress_Att_38 B.ByteString  | Onkeydown_Att_38 B.ByteString  | Onkeyup_Att_38 B.ByteString  | Accesskey_Att_38 B.ByteString 
   deriving (Show)
data Att37 = Cols_Att_37 B.ByteString 
   deriving (Show)
data Att36 = Rows_Att_36 B.ByteString 
   deriving (Show)
data Att35 = Id_Att_35 B.ByteString  | Class_Att_35 B.ByteString  | Style_Att_35 B.ByteString  | Title_Att_35 B.ByteString  | Lang_Att_35 B.ByteString  | Dir_Att_35 B.ByteString  | Onclick_Att_35 B.ByteString  | Ondblclick_Att_35 B.ByteString  | Onmousedown_Att_35 B.ByteString  | Onmouseup_Att_35 B.ByteString  | Onmouseover_Att_35 B.ByteString  | Onmousemove_Att_35 B.ByteString  | Onmouseout_Att_35 B.ByteString  | Onkeypress_Att_35 B.ByteString  | Onkeydown_Att_35 B.ByteString  | Onkeyup_Att_35 B.ByteString  | Accesskey_Att_35 B.ByteString  | Tabindex_Att_35 B.ByteString  | Onfocus_Att_35 B.ByteString  | Onblur_Att_35 B.ByteString  | Name_Att_35 B.ByteString  | Rows_Att_35 B.ByteString  | Cols_Att_35 B.ByteString  | Disabled_Att_35 B.ByteString  | Readonly_Att_35 B.ByteString  | Onselect_Att_35 B.ByteString  | Onchange_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  | Lang_Att_34 B.ByteString  | Dir_Att_34 B.ByteString  | Onclick_Att_34 B.ByteString  | Ondblclick_Att_34 B.ByteString  | Onmousedown_Att_34 B.ByteString  | Onmouseup_Att_34 B.ByteString  | Onmouseover_Att_34 B.ByteString  | Onmousemove_Att_34 B.ByteString  | Onmouseout_Att_34 B.ByteString  | Onkeypress_Att_34 B.ByteString  | Onkeydown_Att_34 B.ByteString  | Onkeyup_Att_34 B.ByteString  | Selected_Att_34 B.ByteString  | Disabled_Att_34 B.ByteString  | Label_Att_34 B.ByteString  | Value_Att_34 B.ByteString 
   deriving (Show)
data Att33 = Label_Att_33 B.ByteString 
   deriving (Show)
data Att32 = Id_Att_32 B.ByteString  | Class_Att_32 B.ByteString  | Style_Att_32 B.ByteString  | Title_Att_32 B.ByteString  | Lang_Att_32 B.ByteString  | Dir_Att_32 B.ByteString  | Onclick_Att_32 B.ByteString  | Ondblclick_Att_32 B.ByteString  | Onmousedown_Att_32 B.ByteString  | Onmouseup_Att_32 B.ByteString  | Onmouseover_Att_32 B.ByteString  | Onmousemove_Att_32 B.ByteString  | Onmouseout_Att_32 B.ByteString  | Onkeypress_Att_32 B.ByteString  | Onkeydown_Att_32 B.ByteString  | Onkeyup_Att_32 B.ByteString  | Disabled_Att_32 B.ByteString  | Label_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  | Name_Att_31 B.ByteString  | Size_Att_31 B.ByteString  | Multiple_Att_31 B.ByteString  | Disabled_Att_31 B.ByteString  | Tabindex_Att_31 B.ByteString  | Onfocus_Att_31 B.ByteString  | Onblur_Att_31 B.ByteString  | Onchange_Att_31 B.ByteString 
   deriving (Show)
data Att30 = Id_Att_30 B.ByteString  | Class_Att_30 B.ByteString  | Style_Att_30 B.ByteString  | Title_Att_30 B.ByteString  | Lang_Att_30 B.ByteString  | Dir_Att_30 B.ByteString  | Onclick_Att_30 B.ByteString  | Ondblclick_Att_30 B.ByteString  | Onmousedown_Att_30 B.ByteString  | Onmouseup_Att_30 B.ByteString  | Onmouseover_Att_30 B.ByteString  | Onmousemove_Att_30 B.ByteString  | Onmouseout_Att_30 B.ByteString  | Onkeypress_Att_30 B.ByteString  | Onkeydown_Att_30 B.ByteString  | Onkeyup_Att_30 B.ByteString  | Accesskey_Att_30 B.ByteString  | Tabindex_Att_30 B.ByteString  | Onfocus_Att_30 B.ByteString  | Onblur_Att_30 B.ByteString  | Type_Att_30 B.ByteString  | Name_Att_30 B.ByteString  | Value_Att_30 B.ByteString  | Checked_Att_30 B.ByteString  | Disabled_Att_30 B.ByteString  | Readonly_Att_30 B.ByteString  | Size_Att_30 B.ByteString  | Maxlength_Att_30 B.ByteString  | Src_Att_30 B.ByteString  | Alt_Att_30 B.ByteString  | Usemap_Att_30 B.ByteString  | Onselect_Att_30 B.ByteString  | Onchange_Att_30 B.ByteString  | Accept_Att_30 B.ByteString 
   deriving (Show)
data Att29 = Id_Att_29 B.ByteString  | Class_Att_29 B.ByteString  | Style_Att_29 B.ByteString  | Title_Att_29 B.ByteString  | Lang_Att_29 B.ByteString  | Dir_Att_29 B.ByteString  | Onclick_Att_29 B.ByteString  | Ondblclick_Att_29 B.ByteString  | Onmousedown_Att_29 B.ByteString  | Onmouseup_Att_29 B.ByteString  | Onmouseover_Att_29 B.ByteString  | Onmousemove_Att_29 B.ByteString  | Onmouseout_Att_29 B.ByteString  | Onkeypress_Att_29 B.ByteString  | Onkeydown_Att_29 B.ByteString  | Onkeyup_Att_29 B.ByteString  | For_Att_29 B.ByteString  | Accesskey_Att_29 B.ByteString  | Onfocus_Att_29 B.ByteString  | Onblur_Att_29 B.ByteString 
   deriving (Show)
data Att28 = Action_Att_28 B.ByteString 
   deriving (Show)
data Att27 = Id_Att_27 B.ByteString  | Class_Att_27 B.ByteString  | Style_Att_27 B.ByteString  | Title_Att_27 B.ByteString  | Lang_Att_27 B.ByteString  | Dir_Att_27 B.ByteString  | Onclick_Att_27 B.ByteString  | Ondblclick_Att_27 B.ByteString  | Onmousedown_Att_27 B.ByteString  | Onmouseup_Att_27 B.ByteString  | Onmouseover_Att_27 B.ByteString  | Onmousemove_Att_27 B.ByteString  | Onmouseout_Att_27 B.ByteString  | Onkeypress_Att_27 B.ByteString  | Onkeydown_Att_27 B.ByteString  | Onkeyup_Att_27 B.ByteString  | Action_Att_27 B.ByteString  | Method_Att_27 B.ByteString  | Enctype_Att_27 B.ByteString  | Onsubmit_Att_27 B.ByteString  | Onreset_Att_27 B.ByteString  | Accept_Att_27 B.ByteString  | Accept_charset_Att_27 B.ByteString 
   deriving (Show)
data Att26 = Id_Att_26 B.ByteString  | Class_Att_26 B.ByteString  | Style_Att_26 B.ByteString  | Title_Att_26 B.ByteString  | Lang_Att_26 B.ByteString  | Dir_Att_26 B.ByteString  | Onclick_Att_26 B.ByteString  | Ondblclick_Att_26 B.ByteString  | Onmousedown_Att_26 B.ByteString  | Onmouseup_Att_26 B.ByteString  | Onmouseover_Att_26 B.ByteString  | Onmousemove_Att_26 B.ByteString  | Onmouseout_Att_26 B.ByteString  | Onkeypress_Att_26 B.ByteString  | Onkeydown_Att_26 B.ByteString  | Onkeyup_Att_26 B.ByteString  | Accesskey_Att_26 B.ByteString  | Tabindex_Att_26 B.ByteString  | Onfocus_Att_26 B.ByteString  | Onblur_Att_26 B.ByteString  | Shape_Att_26 B.ByteString  | Coords_Att_26 B.ByteString  | Href_Att_26 B.ByteString  | Nohref_Att_26 B.ByteString  | Alt_Att_26 B.ByteString 
   deriving (Show)
data Att25 = Id_Att_25 B.ByteString 
   deriving (Show)
data Att24 = 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  | Id_Att_24 B.ByteString  | Class_Att_24 B.ByteString  | Style_Att_24 B.ByteString  | Title_Att_24 B.ByteString  | Name_Att_24 B.ByteString 
   deriving (Show)
data Att23 = Alt_Att_23 B.ByteString 
   deriving (Show)
data Att22 = Src_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  | Src_Att_21 B.ByteString  | Alt_Att_21 B.ByteString  | Longdesc_Att_21 B.ByteString  | Height_Att_21 B.ByteString  | Width_Att_21 B.ByteString  | Usemap_Att_21 B.ByteString  | Ismap_Att_21 B.ByteString 
   deriving (Show)
data Att20 = Id_Att_20 B.ByteString  | Name_Att_20 B.ByteString  | Value_Att_20 B.ByteString  | Valuetype_Att_20 B.ByteString  | Type_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  | Declare_Att_19 B.ByteString  | Classid_Att_19 B.ByteString  | Codebase_Att_19 B.ByteString  | Data_Att_19 B.ByteString  | Type_Att_19 B.ByteString  | Codetype_Att_19 B.ByteString  | Archive_Att_19 B.ByteString  | Standby_Att_19 B.ByteString  | Height_Att_19 B.ByteString  | Width_Att_19 B.ByteString  | Usemap_Att_19 B.ByteString  | Name_Att_19 B.ByteString  | Tabindex_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 
   deriving (Show)
data Att17 = Dir_Att_17 B.ByteString 
   deriving (Show)
data Att16 = Id_Att_16 B.ByteString  | Class_Att_16 B.ByteString  | Style_Att_16 B.ByteString  | Title_Att_16 B.ByteString  | 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  | Lang_Att_16 B.ByteString  | Dir_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  | Accesskey_Att_15 B.ByteString  | Tabindex_Att_15 B.ByteString  | Onfocus_Att_15 B.ByteString  | Onblur_Att_15 B.ByteString  | Charset_Att_15 B.ByteString  | Type_Att_15 B.ByteString  | Name_Att_15 B.ByteString  | Href_Att_15 B.ByteString  | Hreflang_Att_15 B.ByteString  | Rel_Att_15 B.ByteString  | Rev_Att_15 B.ByteString  | Shape_Att_15 B.ByteString  | Coords_Att_15 B.ByteString 
   deriving (Show)
data Att14 = Id_Att_14 B.ByteString  | Class_Att_14 B.ByteString  | Style_Att_14 B.ByteString  | Title_Att_14 B.ByteString  | Lang_Att_14 B.ByteString  | Dir_Att_14 B.ByteString  | Onclick_Att_14 B.ByteString  | Ondblclick_Att_14 B.ByteString  | Onmousedown_Att_14 B.ByteString  | Onmouseup_Att_14 B.ByteString  | Onmouseover_Att_14 B.ByteString  | Onmousemove_Att_14 B.ByteString  | Onmouseout_Att_14 B.ByteString  | Onkeypress_Att_14 B.ByteString  | Onkeydown_Att_14 B.ByteString  | Onkeyup_Att_14 B.ByteString  | Cite_Att_14 B.ByteString  | Datetime_Att_14 B.ByteString 
   deriving (Show)
data Att13 = Id_Att_13 B.ByteString  | Class_Att_13 B.ByteString  | Style_Att_13 B.ByteString  | Title_Att_13 B.ByteString  | Lang_Att_13 B.ByteString  | Dir_Att_13 B.ByteString  | Onclick_Att_13 B.ByteString  | Ondblclick_Att_13 B.ByteString  | Onmousedown_Att_13 B.ByteString  | Onmouseup_Att_13 B.ByteString  | Onmouseover_Att_13 B.ByteString  | Onmousemove_Att_13 B.ByteString  | Onmouseout_Att_13 B.ByteString  | Onkeypress_Att_13 B.ByteString  | Onkeydown_Att_13 B.ByteString  | Onkeyup_Att_13 B.ByteString  | Cite_Att_13 B.ByteString 
   deriving (Show)
data Att12 = Id_Att_12 B.ByteString  | Class_Att_12 B.ByteString  | Style_Att_12 B.ByteString  | Title_Att_12 B.ByteString  | Lang_Att_12 B.ByteString  | Dir_Att_12 B.ByteString  | Onclick_Att_12 B.ByteString  | Ondblclick_Att_12 B.ByteString  | Onmousedown_Att_12 B.ByteString  | Onmouseup_Att_12 B.ByteString  | Onmouseover_Att_12 B.ByteString  | Onmousemove_Att_12 B.ByteString  | Onmouseout_Att_12 B.ByteString  | Onkeypress_Att_12 B.ByteString  | Onkeydown_Att_12 B.ByteString  | Onkeyup_Att_12 B.ByteString  | Onload_Att_12 B.ByteString  | Onunload_Att_12 B.ByteString 
   deriving (Show)
data Att11 = Id_Att_11 B.ByteString  | Class_Att_11 B.ByteString  | Style_Att_11 B.ByteString  | Title_Att_11 B.ByteString  | Lang_Att_11 B.ByteString  | Dir_Att_11 B.ByteString  | Onclick_Att_11 B.ByteString  | Ondblclick_Att_11 B.ByteString  | Onmousedown_Att_11 B.ByteString  | Onmouseup_Att_11 B.ByteString  | Onmouseover_Att_11 B.ByteString  | Onmousemove_Att_11 B.ByteString  | Onmouseout_Att_11 B.ByteString  | Onkeypress_Att_11 B.ByteString  | Onkeydown_Att_11 B.ByteString  | Onkeyup_Att_11 B.ByteString 
   deriving (Show)
data Att10 = Id_Att_10 B.ByteString  | Charset_Att_10 B.ByteString  | Type_Att_10 B.ByteString  | Src_Att_10 B.ByteString  | Defer_Att_10 B.ByteString 
   deriving (Show)
data Att9 = Type_Att_9 B.ByteString 
   deriving (Show)
data Att8 = Lang_Att_8 B.ByteString  | Dir_Att_8 B.ByteString  | Id_Att_8 B.ByteString  | Type_Att_8 B.ByteString  | Media_Att_8 B.ByteString  | Title_Att_8 B.ByteString 
   deriving (Show)
data Att7 = Id_Att_7 B.ByteString  | Class_Att_7 B.ByteString  | Style_Att_7 B.ByteString  | Title_Att_7 B.ByteString  | Lang_Att_7 B.ByteString  | Dir_Att_7 B.ByteString  | Onclick_Att_7 B.ByteString  | Ondblclick_Att_7 B.ByteString  | Onmousedown_Att_7 B.ByteString  | Onmouseup_Att_7 B.ByteString  | Onmouseover_Att_7 B.ByteString  | Onmousemove_Att_7 B.ByteString  | Onmouseout_Att_7 B.ByteString  | Onkeypress_Att_7 B.ByteString  | Onkeydown_Att_7 B.ByteString  | Onkeyup_Att_7 B.ByteString  | Charset_Att_7 B.ByteString  | Href_Att_7 B.ByteString  | Hreflang_Att_7 B.ByteString  | Type_Att_7 B.ByteString  | Rel_Att_7 B.ByteString  | Rev_Att_7 B.ByteString  | Media_Att_7 B.ByteString 
   deriving (Show)
data Att6 = Content_Att_6 B.ByteString 
   deriving (Show)
data Att5 = Lang_Att_5 B.ByteString  | Dir_Att_5 B.ByteString  | Id_Att_5 B.ByteString  | Http_equiv_Att_5 B.ByteString  | Name_Att_5 B.ByteString  | Content_Att_5 B.ByteString  | Scheme_Att_5 B.ByteString 
   deriving (Show)
data Att4 = Href_Att_4 B.ByteString 
   deriving (Show)
data Att3 = Href_Att_3 B.ByteString  | Id_Att_3 B.ByteString 
   deriving (Show)
data Att2 = Lang_Att_2 B.ByteString  | Dir_Att_2 B.ByteString  | Id_Att_2 B.ByteString 
   deriving (Show)
data Att1 = Lang_Att_1 B.ByteString  | Dir_Att_1 B.ByteString  | Id_Att_1 B.ByteString  | Profile_Att_1 B.ByteString 
   deriving (Show)
data Att0 = Lang_Att_0 B.ByteString  | Dir_Att_0 B.ByteString  | Id_Att_0 B.ByteString  | Xmlns_Att_0 B.ByteString 
   deriving (Show)

data ValuetypeEnum = Data | Ref | Object
instance Show ValuetypeEnum where
    show Text.CHXHtml.XHtml1_strict.Data="data"
    show Text.CHXHtml.XHtml1_strict.Ref="ref"
    show Text.CHXHtml.XHtml1_strict.Object="object"
data RulesEnum = Rules_none | Groups | Rows | Cols | Rules_all
instance Show RulesEnum where
    show Text.CHXHtml.XHtml1_strict.Rules_none="none"
    show Text.CHXHtml.XHtml1_strict.Groups="groups"
    show Text.CHXHtml.XHtml1_strict.Rows="rows"
    show Text.CHXHtml.XHtml1_strict.Cols="cols"
    show Text.CHXHtml.XHtml1_strict.Rules_all="all"
data ShapeEnum = Rect | Circle | Poly | Default
instance Show ShapeEnum where
    show Text.CHXHtml.XHtml1_strict.Rect="rect"
    show Text.CHXHtml.XHtml1_strict.Circle="circle"
    show Text.CHXHtml.XHtml1_strict.Poly="poly"
    show Text.CHXHtml.XHtml1_strict.Default="default"
data MethodEnum = Get | Post
instance Show MethodEnum where
    show Text.CHXHtml.XHtml1_strict.Get="get"
    show Text.CHXHtml.XHtml1_strict.Post="post"
data DirEnum = Ltr | Rtl
instance Show DirEnum where
    show Text.CHXHtml.XHtml1_strict.Ltr="ltr"
    show Text.CHXHtml.XHtml1_strict.Rtl="rtl"
data FrameEnum = Void | Above | Below | Hsides | Lhs | Rhs | Vsides | Box | Border
instance Show FrameEnum where
    show Text.CHXHtml.XHtml1_strict.Void="void"
    show Text.CHXHtml.XHtml1_strict.Above="above"
    show Text.CHXHtml.XHtml1_strict.Below="below"
    show Text.CHXHtml.XHtml1_strict.Hsides="hsides"
    show Text.CHXHtml.XHtml1_strict.Lhs="lhs"
    show Text.CHXHtml.XHtml1_strict.Rhs="rhs"
    show Text.CHXHtml.XHtml1_strict.Vsides="vsides"
    show Text.CHXHtml.XHtml1_strict.Box="box"
    show Text.CHXHtml.XHtml1_strict.Border="border"
data ValignEnum = Top | Middle | Bottom | Baseline
instance Show ValignEnum where
    show Text.CHXHtml.XHtml1_strict.Top="top"
    show Text.CHXHtml.XHtml1_strict.Middle="middle"
    show Text.CHXHtml.XHtml1_strict.Bottom="bottom"
    show Text.CHXHtml.XHtml1_strict.Baseline="baseline"
data AlignEnum = Align_left | Center | Align_right | Justify | Char
instance Show AlignEnum where
    show Text.CHXHtml.XHtml1_strict.Align_left="left"
    show Text.CHXHtml.XHtml1_strict.Center="center"
    show Text.CHXHtml.XHtml1_strict.Align_right="right"
    show Text.CHXHtml.XHtml1_strict.Justify="justify"
    show Text.CHXHtml.XHtml1_strict.Char="char"
data ScopeEnum = Row | Col | Rowgroup | Colgroup
instance Show ScopeEnum where
    show Text.CHXHtml.XHtml1_strict.Row="row"
    show Text.CHXHtml.XHtml1_strict.Col="col"
    show Text.CHXHtml.XHtml1_strict.Rowgroup="rowgroup"
    show Text.CHXHtml.XHtml1_strict.Colgroup="colgroup"

class A_Http_equiv a where
    http_equiv_att :: String -> a
    http_equiv_att_bs :: B.ByteString -> a
instance A_Http_equiv Att5 where
    http_equiv_att s =  Http_equiv_Att_5 (s2b_escape s)
    http_equiv_att_bs =  Http_equiv_Att_5 

class A_Content a where
    content_att :: String -> a
    content_att_bs :: B.ByteString -> a
instance A_Content Att6 where
    content_att s =  Content_Att_6 (s2b_escape s)
    content_att_bs =  Content_Att_6 
instance A_Content Att5 where
    content_att s =  Content_Att_5 (s2b_escape s)
    content_att_bs =  Content_Att_5 

class A_Nohref a where
    nohref_att :: String -> a
instance A_Nohref Att26 where
    nohref_att s =  Nohref_Att_26 (s2b (show s))

class A_Onkeydown a where
    onkeydown_att :: String -> a
    onkeydown_att_bs :: B.ByteString -> a
instance A_Onkeydown Att43 where
    onkeydown_att s =  Onkeydown_Att_43 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_43 
instance A_Onkeydown Att42 where
    onkeydown_att s =  Onkeydown_Att_42 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_42 
instance A_Onkeydown Att41 where
    onkeydown_att s =  Onkeydown_Att_41 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_41 
instance A_Onkeydown Att40 where
    onkeydown_att s =  Onkeydown_Att_40 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_40 
instance A_Onkeydown Att39 where
    onkeydown_att s =  Onkeydown_Att_39 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_39 
instance A_Onkeydown Att38 where
    onkeydown_att s =  Onkeydown_Att_38 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_38 
instance A_Onkeydown Att35 where
    onkeydown_att s =  Onkeydown_Att_35 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_35 
instance A_Onkeydown Att34 where
    onkeydown_att s =  Onkeydown_Att_34 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_34 
instance A_Onkeydown Att32 where
    onkeydown_att s =  Onkeydown_Att_32 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_32 
instance A_Onkeydown Att31 where
    onkeydown_att s =  Onkeydown_Att_31 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_31 
instance A_Onkeydown Att30 where
    onkeydown_att s =  Onkeydown_Att_30 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_30 
instance A_Onkeydown Att29 where
    onkeydown_att s =  Onkeydown_Att_29 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_29 
instance A_Onkeydown Att27 where
    onkeydown_att s =  Onkeydown_Att_27 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_27 
instance A_Onkeydown Att26 where
    onkeydown_att s =  Onkeydown_Att_26 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_26 
instance A_Onkeydown Att24 where
    onkeydown_att s =  Onkeydown_Att_24 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_24 
instance A_Onkeydown Att21 where
    onkeydown_att s =  Onkeydown_Att_21 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_21 
instance A_Onkeydown Att19 where
    onkeydown_att s =  Onkeydown_Att_19 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_19 
instance A_Onkeydown Att16 where
    onkeydown_att s =  Onkeydown_Att_16 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_16 
instance A_Onkeydown Att15 where
    onkeydown_att s =  Onkeydown_Att_15 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_15 
instance A_Onkeydown Att14 where
    onkeydown_att s =  Onkeydown_Att_14 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_14 
instance A_Onkeydown Att13 where
    onkeydown_att s =  Onkeydown_Att_13 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_13 
instance A_Onkeydown Att12 where
    onkeydown_att s =  Onkeydown_Att_12 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_12 
instance A_Onkeydown Att11 where
    onkeydown_att s =  Onkeydown_Att_11 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_11 
instance A_Onkeydown Att7 where
    onkeydown_att s =  Onkeydown_Att_7 (s2b_escape s)
    onkeydown_att_bs =  Onkeydown_Att_7 

class A_Onkeyup a where
    onkeyup_att :: String -> a
    onkeyup_att_bs :: B.ByteString -> a
instance A_Onkeyup Att43 where
    onkeyup_att s =  Onkeyup_Att_43 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_43 
instance A_Onkeyup Att42 where
    onkeyup_att s =  Onkeyup_Att_42 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_42 
instance A_Onkeyup Att41 where
    onkeyup_att s =  Onkeyup_Att_41 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_41 
instance A_Onkeyup Att40 where
    onkeyup_att s =  Onkeyup_Att_40 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_40 
instance A_Onkeyup Att39 where
    onkeyup_att s =  Onkeyup_Att_39 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_39 
instance A_Onkeyup Att38 where
    onkeyup_att s =  Onkeyup_Att_38 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_38 
instance A_Onkeyup Att35 where
    onkeyup_att s =  Onkeyup_Att_35 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_35 
instance A_Onkeyup Att34 where
    onkeyup_att s =  Onkeyup_Att_34 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_34 
instance A_Onkeyup Att32 where
    onkeyup_att s =  Onkeyup_Att_32 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_32 
instance A_Onkeyup Att31 where
    onkeyup_att s =  Onkeyup_Att_31 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_31 
instance A_Onkeyup Att30 where
    onkeyup_att s =  Onkeyup_Att_30 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_30 
instance A_Onkeyup Att29 where
    onkeyup_att s =  Onkeyup_Att_29 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_29 
instance A_Onkeyup Att27 where
    onkeyup_att s =  Onkeyup_Att_27 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_27 
instance A_Onkeyup Att26 where
    onkeyup_att s =  Onkeyup_Att_26 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_26 
instance A_Onkeyup Att24 where
    onkeyup_att s =  Onkeyup_Att_24 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_24 
instance A_Onkeyup Att21 where
    onkeyup_att s =  Onkeyup_Att_21 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_21 
instance A_Onkeyup Att19 where
    onkeyup_att s =  Onkeyup_Att_19 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_19 
instance A_Onkeyup Att16 where
    onkeyup_att s =  Onkeyup_Att_16 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_16 
instance A_Onkeyup Att15 where
    onkeyup_att s =  Onkeyup_Att_15 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_15 
instance A_Onkeyup Att14 where
    onkeyup_att s =  Onkeyup_Att_14 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_14 
instance A_Onkeyup Att13 where
    onkeyup_att s =  Onkeyup_Att_13 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_13 
instance A_Onkeyup Att12 where
    onkeyup_att s =  Onkeyup_Att_12 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_12 
instance A_Onkeyup Att11 where
    onkeyup_att s =  Onkeyup_Att_11 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_11 
instance A_Onkeyup Att7 where
    onkeyup_att s =  Onkeyup_Att_7 (s2b_escape s)
    onkeyup_att_bs =  Onkeyup_Att_7 

class A_Onreset a where
    onreset_att :: String -> a
    onreset_att_bs :: B.ByteString -> a
instance A_Onreset Att27 where
    onreset_att s =  Onreset_Att_27 (s2b_escape s)
    onreset_att_bs =  Onreset_Att_27 

class A_Onmouseup a where
    onmouseup_att :: String -> a
    onmouseup_att_bs :: B.ByteString -> a
instance A_Onmouseup Att43 where
    onmouseup_att s =  Onmouseup_Att_43 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_43 
instance A_Onmouseup Att42 where
    onmouseup_att s =  Onmouseup_Att_42 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_42 
instance A_Onmouseup Att41 where
    onmouseup_att s =  Onmouseup_Att_41 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_41 
instance A_Onmouseup Att40 where
    onmouseup_att s =  Onmouseup_Att_40 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_40 
instance A_Onmouseup Att39 where
    onmouseup_att s =  Onmouseup_Att_39 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_39 
instance A_Onmouseup Att38 where
    onmouseup_att s =  Onmouseup_Att_38 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_38 
instance A_Onmouseup Att35 where
    onmouseup_att s =  Onmouseup_Att_35 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_35 
instance A_Onmouseup Att34 where
    onmouseup_att s =  Onmouseup_Att_34 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_34 
instance A_Onmouseup Att32 where
    onmouseup_att s =  Onmouseup_Att_32 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_32 
instance A_Onmouseup Att31 where
    onmouseup_att s =  Onmouseup_Att_31 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_31 
instance A_Onmouseup Att30 where
    onmouseup_att s =  Onmouseup_Att_30 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_30 
instance A_Onmouseup Att29 where
    onmouseup_att s =  Onmouseup_Att_29 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_29 
instance A_Onmouseup Att27 where
    onmouseup_att s =  Onmouseup_Att_27 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_27 
instance A_Onmouseup Att26 where
    onmouseup_att s =  Onmouseup_Att_26 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_26 
instance A_Onmouseup Att24 where
    onmouseup_att s =  Onmouseup_Att_24 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_24 
instance A_Onmouseup Att21 where
    onmouseup_att s =  Onmouseup_Att_21 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_21 
instance A_Onmouseup Att19 where
    onmouseup_att s =  Onmouseup_Att_19 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_19 
instance A_Onmouseup Att16 where
    onmouseup_att s =  Onmouseup_Att_16 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_16 
instance A_Onmouseup Att15 where
    onmouseup_att s =  Onmouseup_Att_15 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_15 
instance A_Onmouseup Att14 where
    onmouseup_att s =  Onmouseup_Att_14 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_14 
instance A_Onmouseup Att13 where
    onmouseup_att s =  Onmouseup_Att_13 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_13 
instance A_Onmouseup Att12 where
    onmouseup_att s =  Onmouseup_Att_12 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_12 
instance A_Onmouseup Att11 where
    onmouseup_att s =  Onmouseup_Att_11 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_11 
instance A_Onmouseup Att7 where
    onmouseup_att s =  Onmouseup_Att_7 (s2b_escape s)
    onmouseup_att_bs =  Onmouseup_Att_7 

class A_Scope a where
    scope_att :: ScopeEnum -> a
instance A_Scope Att43 where
    scope_att s =  Scope_Att_43 (s2b (show s))

class A_Onmouseover a where
    onmouseover_att :: String -> a
    onmouseover_att_bs :: B.ByteString -> a
instance A_Onmouseover Att43 where
    onmouseover_att s =  Onmouseover_Att_43 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_43 
instance A_Onmouseover Att42 where
    onmouseover_att s =  Onmouseover_Att_42 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_42 
instance A_Onmouseover Att41 where
    onmouseover_att s =  Onmouseover_Att_41 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_41 
instance A_Onmouseover Att40 where
    onmouseover_att s =  Onmouseover_Att_40 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_40 
instance A_Onmouseover Att39 where
    onmouseover_att s =  Onmouseover_Att_39 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_39 
instance A_Onmouseover Att38 where
    onmouseover_att s =  Onmouseover_Att_38 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_38 
instance A_Onmouseover Att35 where
    onmouseover_att s =  Onmouseover_Att_35 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_35 
instance A_Onmouseover Att34 where
    onmouseover_att s =  Onmouseover_Att_34 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_34 
instance A_Onmouseover Att32 where
    onmouseover_att s =  Onmouseover_Att_32 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_32 
instance A_Onmouseover Att31 where
    onmouseover_att s =  Onmouseover_Att_31 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_31 
instance A_Onmouseover Att30 where
    onmouseover_att s =  Onmouseover_Att_30 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_30 
instance A_Onmouseover Att29 where
    onmouseover_att s =  Onmouseover_Att_29 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_29 
instance A_Onmouseover Att27 where
    onmouseover_att s =  Onmouseover_Att_27 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_27 
instance A_Onmouseover Att26 where
    onmouseover_att s =  Onmouseover_Att_26 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_26 
instance A_Onmouseover Att24 where
    onmouseover_att s =  Onmouseover_Att_24 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_24 
instance A_Onmouseover Att21 where
    onmouseover_att s =  Onmouseover_Att_21 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_21 
instance A_Onmouseover Att19 where
    onmouseover_att s =  Onmouseover_Att_19 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_19 
instance A_Onmouseover Att16 where
    onmouseover_att s =  Onmouseover_Att_16 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_16 
instance A_Onmouseover Att15 where
    onmouseover_att s =  Onmouseover_Att_15 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_15 
instance A_Onmouseover Att14 where
    onmouseover_att s =  Onmouseover_Att_14 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_14 
instance A_Onmouseover Att13 where
    onmouseover_att s =  Onmouseover_Att_13 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_13 
instance A_Onmouseover Att12 where
    onmouseover_att s =  Onmouseover_Att_12 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_12 
instance A_Onmouseover Att11 where
    onmouseover_att s =  Onmouseover_Att_11 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_11 
instance A_Onmouseover Att7 where
    onmouseover_att s =  Onmouseover_Att_7 (s2b_escape s)
    onmouseover_att_bs =  Onmouseover_Att_7 

class A_Align a where
    align_att :: AlignEnum -> a
instance A_Align Att43 where
    align_att s =  Align_Att_43 (s2b (show s))
instance A_Align Att42 where
    align_att s =  Align_Att_42 (s2b (show s))
instance A_Align Att41 where
    align_att s =  Align_Att_41 (s2b (show s))

class A_Lang a where
    lang_att :: String -> a
    lang_att_bs :: B.ByteString -> a
instance A_Lang Att43 where
    lang_att s =  Lang_Att_43 (s2b_escape s)
    lang_att_bs =  Lang_Att_43 
instance A_Lang Att42 where
    lang_att s =  Lang_Att_42 (s2b_escape s)
    lang_att_bs =  Lang_Att_42 
instance A_Lang Att41 where
    lang_att s =  Lang_Att_41 (s2b_escape s)
    lang_att_bs =  Lang_Att_41 
instance A_Lang Att40 where
    lang_att s =  Lang_Att_40 (s2b_escape s)
    lang_att_bs =  Lang_Att_40 
instance A_Lang Att39 where
    lang_att s =  Lang_Att_39 (s2b_escape s)
    lang_att_bs =  Lang_Att_39 
instance A_Lang Att38 where
    lang_att s =  Lang_Att_38 (s2b_escape s)
    lang_att_bs =  Lang_Att_38 
instance A_Lang Att35 where
    lang_att s =  Lang_Att_35 (s2b_escape s)
    lang_att_bs =  Lang_Att_35 
instance A_Lang Att34 where
    lang_att s =  Lang_Att_34 (s2b_escape s)
    lang_att_bs =  Lang_Att_34 
instance A_Lang Att32 where
    lang_att s =  Lang_Att_32 (s2b_escape s)
    lang_att_bs =  Lang_Att_32 
instance A_Lang Att31 where
    lang_att s =  Lang_Att_31 (s2b_escape s)
    lang_att_bs =  Lang_Att_31 
instance A_Lang Att30 where
    lang_att s =  Lang_Att_30 (s2b_escape s)
    lang_att_bs =  Lang_Att_30 
instance A_Lang Att29 where
    lang_att s =  Lang_Att_29 (s2b_escape s)
    lang_att_bs =  Lang_Att_29 
instance A_Lang Att27 where
    lang_att s =  Lang_Att_27 (s2b_escape s)
    lang_att_bs =  Lang_Att_27 
instance A_Lang Att26 where
    lang_att s =  Lang_Att_26 (s2b_escape s)
    lang_att_bs =  Lang_Att_26 
instance A_Lang Att24 where
    lang_att s =  Lang_Att_24 (s2b_escape s)
    lang_att_bs =  Lang_Att_24 
instance A_Lang Att21 where
    lang_att s =  Lang_Att_21 (s2b_escape s)
    lang_att_bs =  Lang_Att_21 
instance A_Lang Att19 where
    lang_att s =  Lang_Att_19 (s2b_escape s)
    lang_att_bs =  Lang_Att_19 
instance A_Lang Att16 where
    lang_att s =  Lang_Att_16 (s2b_escape s)
    lang_att_bs =  Lang_Att_16 
instance A_Lang Att15 where
    lang_att s =  Lang_Att_15 (s2b_escape s)
    lang_att_bs =  Lang_Att_15 
instance A_Lang Att14 where
    lang_att s =  Lang_Att_14 (s2b_escape s)
    lang_att_bs =  Lang_Att_14 
instance A_Lang Att13 where
    lang_att s =  Lang_Att_13 (s2b_escape s)
    lang_att_bs =  Lang_Att_13 
instance A_Lang Att12 where
    lang_att s =  Lang_Att_12 (s2b_escape s)
    lang_att_bs =  Lang_Att_12 
instance A_Lang Att11 where
    lang_att s =  Lang_Att_11 (s2b_escape s)
    lang_att_bs =  Lang_Att_11 
instance A_Lang Att8 where
    lang_att s =  Lang_Att_8 (s2b_escape s)
    lang_att_bs =  Lang_Att_8 
instance A_Lang Att7 where
    lang_att s =  Lang_Att_7 (s2b_escape s)
    lang_att_bs =  Lang_Att_7 
instance A_Lang Att5 where
    lang_att s =  Lang_Att_5 (s2b_escape s)
    lang_att_bs =  Lang_Att_5 
instance A_Lang Att2 where
    lang_att s =  Lang_Att_2 (s2b_escape s)
    lang_att_bs =  Lang_Att_2 
instance A_Lang Att1 where
    lang_att s =  Lang_Att_1 (s2b_escape s)
    lang_att_bs =  Lang_Att_1 
instance A_Lang Att0 where
    lang_att s =  Lang_Att_0 (s2b_escape s)
    lang_att_bs =  Lang_Att_0 

class A_Valign a where
    valign_att :: ValignEnum -> a
instance A_Valign Att43 where
    valign_att s =  Valign_Att_43 (s2b (show s))
instance A_Valign Att42 where
    valign_att s =  Valign_Att_42 (s2b (show s))
instance A_Valign Att41 where
    valign_att s =  Valign_Att_41 (s2b (show s))

class A_Name a where
    name_att :: String -> a
    name_att_bs :: B.ByteString -> a
instance A_Name Att39 where
    name_att s =  Name_Att_39 (s2b_escape s)
    name_att_bs =  Name_Att_39 
instance A_Name Att35 where
    name_att s =  Name_Att_35 (s2b_escape s)
    name_att_bs =  Name_Att_35 
instance A_Name Att31 where
    name_att s =  Name_Att_31 (s2b_escape s)
    name_att_bs =  Name_Att_31 
instance A_Name Att30 where
    name_att s =  Name_Att_30 (s2b_escape s)
    name_att_bs =  Name_Att_30 
instance A_Name Att24 where
    name_att s =  Name_Att_24 (s2b_escape s)
    name_att_bs =  Name_Att_24 
instance A_Name Att20 where
    name_att s =  Name_Att_20 (s2b_escape s)
    name_att_bs =  Name_Att_20 
instance A_Name Att19 where
    name_att s =  Name_Att_19 (s2b_escape s)
    name_att_bs =  Name_Att_19 
instance A_Name Att15 where
    name_att s =  Name_Att_15 (s2b_escape s)
    name_att_bs =  Name_Att_15 
instance A_Name Att5 where
    name_att s =  Name_Att_5 (s2b_escape s)
    name_att_bs =  Name_Att_5 

class A_Charset a where
    charset_att :: String -> a
    charset_att_bs :: B.ByteString -> a
instance A_Charset Att15 where
    charset_att s =  Charset_Att_15 (s2b_escape s)
    charset_att_bs =  Charset_Att_15 
instance A_Charset Att10 where
    charset_att s =  Charset_Att_10 (s2b_escape s)
    charset_att_bs =  Charset_Att_10 
instance A_Charset Att7 where
    charset_att s =  Charset_Att_7 (s2b_escape s)
    charset_att_bs =  Charset_Att_7 

class A_Scheme a where
    scheme_att :: String -> a
    scheme_att_bs :: B.ByteString -> a
instance A_Scheme Att5 where
    scheme_att s =  Scheme_Att_5 (s2b_escape s)
    scheme_att_bs =  Scheme_Att_5 

class A_Accept_charset a where
    accept_charset_att :: String -> a
    accept_charset_att_bs :: B.ByteString -> a
instance A_Accept_charset Att27 where
    accept_charset_att s =  Accept_charset_Att_27 (s2b_escape s)
    accept_charset_att_bs =  Accept_charset_Att_27 

class A_Onmousedown a where
    onmousedown_att :: String -> a
    onmousedown_att_bs :: B.ByteString -> a
instance A_Onmousedown Att43 where
    onmousedown_att s =  Onmousedown_Att_43 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_43 
instance A_Onmousedown Att42 where
    onmousedown_att s =  Onmousedown_Att_42 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_42 
instance A_Onmousedown Att41 where
    onmousedown_att s =  Onmousedown_Att_41 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_41 
instance A_Onmousedown Att40 where
    onmousedown_att s =  Onmousedown_Att_40 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_40 
instance A_Onmousedown Att39 where
    onmousedown_att s =  Onmousedown_Att_39 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_39 
instance A_Onmousedown Att38 where
    onmousedown_att s =  Onmousedown_Att_38 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_38 
instance A_Onmousedown Att35 where
    onmousedown_att s =  Onmousedown_Att_35 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_35 
instance A_Onmousedown Att34 where
    onmousedown_att s =  Onmousedown_Att_34 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_34 
instance A_Onmousedown Att32 where
    onmousedown_att s =  Onmousedown_Att_32 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_32 
instance A_Onmousedown Att31 where
    onmousedown_att s =  Onmousedown_Att_31 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_31 
instance A_Onmousedown Att30 where
    onmousedown_att s =  Onmousedown_Att_30 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_30 
instance A_Onmousedown Att29 where
    onmousedown_att s =  Onmousedown_Att_29 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_29 
instance A_Onmousedown Att27 where
    onmousedown_att s =  Onmousedown_Att_27 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_27 
instance A_Onmousedown Att26 where
    onmousedown_att s =  Onmousedown_Att_26 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_26 
instance A_Onmousedown Att24 where
    onmousedown_att s =  Onmousedown_Att_24 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_24 
instance A_Onmousedown Att21 where
    onmousedown_att s =  Onmousedown_Att_21 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_21 
instance A_Onmousedown Att19 where
    onmousedown_att s =  Onmousedown_Att_19 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_19 
instance A_Onmousedown Att16 where
    onmousedown_att s =  Onmousedown_Att_16 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_16 
instance A_Onmousedown Att15 where
    onmousedown_att s =  Onmousedown_Att_15 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_15 
instance A_Onmousedown Att14 where
    onmousedown_att s =  Onmousedown_Att_14 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_14 
instance A_Onmousedown Att13 where
    onmousedown_att s =  Onmousedown_Att_13 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_13 
instance A_Onmousedown Att12 where
    onmousedown_att s =  Onmousedown_Att_12 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_12 
instance A_Onmousedown Att11 where
    onmousedown_att s =  Onmousedown_Att_11 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_11 
instance A_Onmousedown Att7 where
    onmousedown_att s =  Onmousedown_Att_7 (s2b_escape s)
    onmousedown_att_bs =  Onmousedown_Att_7 

class A_Rev a where
    rev_att :: String -> a
    rev_att_bs :: B.ByteString -> a
instance A_Rev Att15 where
    rev_att s =  Rev_Att_15 (s2b_escape s)
    rev_att_bs =  Rev_Att_15 
instance A_Rev Att7 where
    rev_att s =  Rev_Att_7 (s2b_escape s)
    rev_att_bs =  Rev_Att_7 

class A_Span a where
    span_att :: String -> a
    span_att_bs :: B.ByteString -> a
instance A_Span Att42 where
    span_att s =  Span_Att_42 (s2b_escape s)
    span_att_bs =  Span_Att_42 

class A_Title a where
    title_att :: String -> a
    title_att_bs :: B.ByteString -> a
instance A_Title Att43 where
    title_att s =  Title_Att_43 (s2b_escape s)
    title_att_bs =  Title_Att_43 
instance A_Title Att42 where
    title_att s =  Title_Att_42 (s2b_escape s)
    title_att_bs =  Title_Att_42 
instance A_Title Att41 where
    title_att s =  Title_Att_41 (s2b_escape s)
    title_att_bs =  Title_Att_41 
instance A_Title Att40 where
    title_att s =  Title_Att_40 (s2b_escape s)
    title_att_bs =  Title_Att_40 
instance A_Title Att39 where
    title_att s =  Title_Att_39 (s2b_escape s)
    title_att_bs =  Title_Att_39 
instance A_Title Att38 where
    title_att s =  Title_Att_38 (s2b_escape s)
    title_att_bs =  Title_Att_38 
instance A_Title Att35 where
    title_att s =  Title_Att_35 (s2b_escape s)
    title_att_bs =  Title_Att_35 
instance A_Title Att34 where
    title_att s =  Title_Att_34 (s2b_escape s)
    title_att_bs =  Title_Att_34 
instance A_Title Att32 where
    title_att s =  Title_Att_32 (s2b_escape s)
    title_att_bs =  Title_Att_32 
instance A_Title Att31 where
    title_att s =  Title_Att_31 (s2b_escape s)
    title_att_bs =  Title_Att_31 
instance A_Title Att30 where
    title_att s =  Title_Att_30 (s2b_escape s)
    title_att_bs =  Title_Att_30 
instance A_Title Att29 where
    title_att s =  Title_Att_29 (s2b_escape s)
    title_att_bs =  Title_Att_29 
instance A_Title Att27 where
    title_att s =  Title_Att_27 (s2b_escape s)
    title_att_bs =  Title_Att_27 
instance A_Title Att26 where
    title_att s =  Title_Att_26 (s2b_escape s)
    title_att_bs =  Title_Att_26 
instance A_Title Att24 where
    title_att s =  Title_Att_24 (s2b_escape s)
    title_att_bs =  Title_Att_24 
instance A_Title Att21 where
    title_att s =  Title_Att_21 (s2b_escape s)
    title_att_bs =  Title_Att_21 
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 Att16 where
    title_att s =  Title_Att_16 (s2b_escape s)
    title_att_bs =  Title_Att_16 
instance A_Title Att15 where
    title_att s =  Title_Att_15 (s2b_escape s)
    title_att_bs =  Title_Att_15 
instance A_Title Att14 where
    title_att s =  Title_Att_14 (s2b_escape s)
    title_att_bs =  Title_Att_14 
instance A_Title Att13 where
    title_att s =  Title_Att_13 (s2b_escape s)
    title_att_bs =  Title_Att_13 
instance A_Title Att12 where
    title_att s =  Title_Att_12 (s2b_escape s)
    title_att_bs =  Title_Att_12 
instance A_Title Att11 where
    title_att s =  Title_Att_11 (s2b_escape s)
    title_att_bs =  Title_Att_11 
instance A_Title Att8 where
    title_att s =  Title_Att_8 (s2b_escape s)
    title_att_bs =  Title_Att_8 
instance A_Title Att7 where
    title_att s =  Title_Att_7 (s2b_escape s)
    title_att_bs =  Title_Att_7 

class A_Onclick a where
    onclick_att :: String -> a
    onclick_att_bs :: B.ByteString -> a
instance A_Onclick Att43 where
    onclick_att s =  Onclick_Att_43 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_43 
instance A_Onclick Att42 where
    onclick_att s =  Onclick_Att_42 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_42 
instance A_Onclick Att41 where
    onclick_att s =  Onclick_Att_41 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_41 
instance A_Onclick Att40 where
    onclick_att s =  Onclick_Att_40 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_40 
instance A_Onclick Att39 where
    onclick_att s =  Onclick_Att_39 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_39 
instance A_Onclick Att38 where
    onclick_att s =  Onclick_Att_38 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_38 
instance A_Onclick Att35 where
    onclick_att s =  Onclick_Att_35 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_35 
instance A_Onclick Att34 where
    onclick_att s =  Onclick_Att_34 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_34 
instance A_Onclick Att32 where
    onclick_att s =  Onclick_Att_32 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_32 
instance A_Onclick Att31 where
    onclick_att s =  Onclick_Att_31 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_31 
instance A_Onclick Att30 where
    onclick_att s =  Onclick_Att_30 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_30 
instance A_Onclick Att29 where
    onclick_att s =  Onclick_Att_29 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_29 
instance A_Onclick Att27 where
    onclick_att s =  Onclick_Att_27 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_27 
instance A_Onclick Att26 where
    onclick_att s =  Onclick_Att_26 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_26 
instance A_Onclick Att24 where
    onclick_att s =  Onclick_Att_24 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_24 
instance A_Onclick Att21 where
    onclick_att s =  Onclick_Att_21 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_21 
instance A_Onclick Att19 where
    onclick_att s =  Onclick_Att_19 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_19 
instance A_Onclick Att16 where
    onclick_att s =  Onclick_Att_16 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_16 
instance A_Onclick Att15 where
    onclick_att s =  Onclick_Att_15 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_15 
instance A_Onclick Att14 where
    onclick_att s =  Onclick_Att_14 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_14 
instance A_Onclick Att13 where
    onclick_att s =  Onclick_Att_13 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_13 
instance A_Onclick Att12 where
    onclick_att s =  Onclick_Att_12 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_12 
instance A_Onclick Att11 where
    onclick_att s =  Onclick_Att_11 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_11 
instance A_Onclick Att7 where
    onclick_att s =  Onclick_Att_7 (s2b_escape s)
    onclick_att_bs =  Onclick_Att_7 

class A_Width a where
    width_att :: String -> a
    width_att_bs :: B.ByteString -> a
instance A_Width Att42 where
    width_att s =  Width_Att_42 (s2b_escape s)
    width_att_bs =  Width_Att_42 
instance A_Width Att40 where
    width_att s =  Width_Att_40 (s2b_escape s)
    width_att_bs =  Width_Att_40 
instance A_Width Att21 where
    width_att s =  Width_Att_21 (s2b_escape s)
    width_att_bs =  Width_Att_21 
instance A_Width Att19 where
    width_att s =  Width_Att_19 (s2b_escape s)
    width_att_bs =  Width_Att_19 

class A_Enctype a where
    enctype_att :: String -> a
    enctype_att_bs :: B.ByteString -> a
instance A_Enctype Att27 where
    enctype_att s =  Enctype_Att_27 (s2b_escape s)
    enctype_att_bs =  Enctype_Att_27 

class A_Ismap a where
    ismap_att :: String -> a
instance A_Ismap Att21 where
    ismap_att s =  Ismap_Att_21 (s2b (show s))

class A_Usemap a where
    usemap_att :: String -> a
    usemap_att_bs :: B.ByteString -> a
instance A_Usemap Att30 where
    usemap_att s =  Usemap_Att_30 (s2b_escape s)
    usemap_att_bs =  Usemap_Att_30 
instance A_Usemap Att21 where
    usemap_att s =  Usemap_Att_21 (s2b_escape s)
    usemap_att_bs =  Usemap_Att_21 
instance A_Usemap Att19 where
    usemap_att s =  Usemap_Att_19 (s2b_escape s)
    usemap_att_bs =  Usemap_Att_19 

class A_Coords a where
    coords_att :: String -> a
    coords_att_bs :: B.ByteString -> a
instance A_Coords Att26 where
    coords_att s =  Coords_Att_26 (s2b_escape s)
    coords_att_bs =  Coords_Att_26 
instance A_Coords Att15 where
    coords_att s =  Coords_Att_15 (s2b_escape s)
    coords_att_bs =  Coords_Att_15 

class A_Frame a where
    frame_att :: FrameEnum -> a
instance A_Frame Att40 where
    frame_att s =  Frame_Att_40 (s2b (show s))

class A_Size a where
    size_att :: String -> a
    size_att_bs :: B.ByteString -> a
instance A_Size Att31 where
    size_att s =  Size_Att_31 (s2b_escape s)
    size_att_bs =  Size_Att_31 
instance A_Size Att30 where
    size_att s =  Size_Att_30 (s2b_escape s)
    size_att_bs =  Size_Att_30 

class A_Onblur a where
    onblur_att :: String -> a
    onblur_att_bs :: B.ByteString -> a
instance A_Onblur Att39 where
    onblur_att s =  Onblur_Att_39 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_39 
instance A_Onblur Att35 where
    onblur_att s =  Onblur_Att_35 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_35 
instance A_Onblur Att31 where
    onblur_att s =  Onblur_Att_31 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_31 
instance A_Onblur Att30 where
    onblur_att s =  Onblur_Att_30 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_30 
instance A_Onblur Att29 where
    onblur_att s =  Onblur_Att_29 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_29 
instance A_Onblur Att26 where
    onblur_att s =  Onblur_Att_26 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_26 
instance A_Onblur Att15 where
    onblur_att s =  Onblur_Att_15 (s2b_escape s)
    onblur_att_bs =  Onblur_Att_15 

class A_Datetime a where
    datetime_att :: String -> a
    datetime_att_bs :: B.ByteString -> a
instance A_Datetime Att14 where
    datetime_att s =  Datetime_Att_14 (s2b_escape s)
    datetime_att_bs =  Datetime_Att_14 

class A_Dir a where
    dir_att :: DirEnum -> a
instance A_Dir Att43 where
    dir_att s =  Dir_Att_43 (s2b (show s))
instance A_Dir Att42 where
    dir_att s =  Dir_Att_42 (s2b (show s))
instance A_Dir Att41 where
    dir_att s =  Dir_Att_41 (s2b (show s))
instance A_Dir Att40 where
    dir_att s =  Dir_Att_40 (s2b (show s))
instance A_Dir Att39 where
    dir_att s =  Dir_Att_39 (s2b (show s))
instance A_Dir Att38 where
    dir_att s =  Dir_Att_38 (s2b (show s))
instance A_Dir Att35 where
    dir_att s =  Dir_Att_35 (s2b (show s))
instance A_Dir Att34 where
    dir_att s =  Dir_Att_34 (s2b (show s))
instance A_Dir Att32 where
    dir_att s =  Dir_Att_32 (s2b (show s))
instance A_Dir Att31 where
    dir_att s =  Dir_Att_31 (s2b (show s))
instance A_Dir Att30 where
    dir_att s =  Dir_Att_30 (s2b (show s))
instance A_Dir Att29 where
    dir_att s =  Dir_Att_29 (s2b (show s))
instance A_Dir Att27 where
    dir_att s =  Dir_Att_27 (s2b (show s))
instance A_Dir Att26 where
    dir_att s =  Dir_Att_26 (s2b (show s))
instance A_Dir Att24 where
    dir_att s =  Dir_Att_24 (s2b (show s))
instance A_Dir Att21 where
    dir_att s =  Dir_Att_21 (s2b (show s))
instance A_Dir Att19 where
    dir_att s =  Dir_Att_19 (s2b (show s))
instance A_Dir Att17 where
    dir_att s =  Dir_Att_17 (s2b (show s))
instance A_Dir Att16 where
    dir_att s =  Dir_Att_16 (s2b (show s))
instance A_Dir Att15 where
    dir_att s =  Dir_Att_15 (s2b (show s))
instance A_Dir Att14 where
    dir_att s =  Dir_Att_14 (s2b (show s))
instance A_Dir Att13 where
    dir_att s =  Dir_Att_13 (s2b (show s))
instance A_Dir Att12 where
    dir_att s =  Dir_Att_12 (s2b (show s))
instance A_Dir Att11 where
    dir_att s =  Dir_Att_11 (s2b (show s))
instance A_Dir Att8 where
    dir_att s =  Dir_Att_8 (s2b (show s))
instance A_Dir Att7 where
    dir_att s =  Dir_Att_7 (s2b (show s))
instance A_Dir Att5 where
    dir_att s =  Dir_Att_5 (s2b (show s))
instance A_Dir Att2 where
    dir_att s =  Dir_Att_2 (s2b (show s))
instance A_Dir Att1 where
    dir_att s =  Dir_Att_1 (s2b (show s))
instance A_Dir Att0 where
    dir_att s =  Dir_Att_0 (s2b (show s))

class A_Summary a where
    summary_att :: String -> a
    summary_att_bs :: B.ByteString -> a
instance A_Summary Att40 where
    summary_att s =  Summary_Att_40 (s2b_escape s)
    summary_att_bs =  Summary_Att_40 

class A_Method a where
    method_att :: MethodEnum -> a
instance A_Method Att27 where
    method_att s =  Method_Att_27 (s2b (show s))

class A_Standby a where
    standby_att :: String -> a
    standby_att_bs :: B.ByteString -> a
instance A_Standby Att19 where
    standby_att s =  Standby_Att_19 (s2b_escape s)
    standby_att_bs =  Standby_Att_19 

class A_Tabindex a where
    tabindex_att :: String -> a
    tabindex_att_bs :: B.ByteString -> a
instance A_Tabindex Att39 where
    tabindex_att s =  Tabindex_Att_39 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_39 
instance A_Tabindex Att35 where
    tabindex_att s =  Tabindex_Att_35 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_35 
instance A_Tabindex Att31 where
    tabindex_att s =  Tabindex_Att_31 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_31 
instance A_Tabindex Att30 where
    tabindex_att s =  Tabindex_Att_30 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_30 
instance A_Tabindex Att26 where
    tabindex_att s =  Tabindex_Att_26 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_26 
instance A_Tabindex Att19 where
    tabindex_att s =  Tabindex_Att_19 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_19 
instance A_Tabindex Att15 where
    tabindex_att s =  Tabindex_Att_15 (s2b_escape s)
    tabindex_att_bs =  Tabindex_Att_15 

class A_Onmousemove a where
    onmousemove_att :: String -> a
    onmousemove_att_bs :: B.ByteString -> a
instance A_Onmousemove Att43 where
    onmousemove_att s =  Onmousemove_Att_43 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_43 
instance A_Onmousemove Att42 where
    onmousemove_att s =  Onmousemove_Att_42 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_42 
instance A_Onmousemove Att41 where
    onmousemove_att s =  Onmousemove_Att_41 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_41 
instance A_Onmousemove Att40 where
    onmousemove_att s =  Onmousemove_Att_40 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_40 
instance A_Onmousemove Att39 where
    onmousemove_att s =  Onmousemove_Att_39 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_39 
instance A_Onmousemove Att38 where
    onmousemove_att s =  Onmousemove_Att_38 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_38 
instance A_Onmousemove Att35 where
    onmousemove_att s =  Onmousemove_Att_35 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_35 
instance A_Onmousemove Att34 where
    onmousemove_att s =  Onmousemove_Att_34 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_34 
instance A_Onmousemove Att32 where
    onmousemove_att s =  Onmousemove_Att_32 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_32 
instance A_Onmousemove Att31 where
    onmousemove_att s =  Onmousemove_Att_31 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_31 
instance A_Onmousemove Att30 where
    onmousemove_att s =  Onmousemove_Att_30 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_30 
instance A_Onmousemove Att29 where
    onmousemove_att s =  Onmousemove_Att_29 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_29 
instance A_Onmousemove Att27 where
    onmousemove_att s =  Onmousemove_Att_27 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_27 
instance A_Onmousemove Att26 where
    onmousemove_att s =  Onmousemove_Att_26 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_26 
instance A_Onmousemove Att24 where
    onmousemove_att s =  Onmousemove_Att_24 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_24 
instance A_Onmousemove Att21 where
    onmousemove_att s =  Onmousemove_Att_21 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_21 
instance A_Onmousemove Att19 where
    onmousemove_att s =  Onmousemove_Att_19 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_19 
instance A_Onmousemove Att16 where
    onmousemove_att s =  Onmousemove_Att_16 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_16 
instance A_Onmousemove Att15 where
    onmousemove_att s =  Onmousemove_Att_15 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_15 
instance A_Onmousemove Att14 where
    onmousemove_att s =  Onmousemove_Att_14 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_14 
instance A_Onmousemove Att13 where
    onmousemove_att s =  Onmousemove_Att_13 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_13 
instance A_Onmousemove Att12 where
    onmousemove_att s =  Onmousemove_Att_12 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_12 
instance A_Onmousemove Att11 where
    onmousemove_att s =  Onmousemove_Att_11 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_11 
instance A_Onmousemove Att7 where
    onmousemove_att s =  Onmousemove_Att_7 (s2b_escape s)
    onmousemove_att_bs =  Onmousemove_Att_7 

class A_Style a where
    style_att :: String -> a
    style_att_bs :: B.ByteString -> a
instance A_Style Att43 where
    style_att s =  Style_Att_43 (s2b_escape s)
    style_att_bs =  Style_Att_43 
instance A_Style Att42 where
    style_att s =  Style_Att_42 (s2b_escape s)
    style_att_bs =  Style_Att_42 
instance A_Style Att41 where
    style_att s =  Style_Att_41 (s2b_escape s)
    style_att_bs =  Style_Att_41 
instance A_Style Att40 where
    style_att s =  Style_Att_40 (s2b_escape s)
    style_att_bs =  Style_Att_40 
instance A_Style Att39 where
    style_att s =  Style_Att_39 (s2b_escape s)
    style_att_bs =  Style_Att_39 
instance A_Style Att38 where
    style_att s =  Style_Att_38 (s2b_escape s)
    style_att_bs =  Style_Att_38 
instance A_Style Att35 where
    style_att s =  Style_Att_35 (s2b_escape s)
    style_att_bs =  Style_Att_35 
instance A_Style Att34 where
    style_att s =  Style_Att_34 (s2b_escape s)
    style_att_bs =  Style_Att_34 
instance A_Style Att32 where
    style_att s =  Style_Att_32 (s2b_escape s)
    style_att_bs =  Style_Att_32 
instance A_Style Att31 where
    style_att s =  Style_Att_31 (s2b_escape s)
    style_att_bs =  Style_Att_31 
instance A_Style Att30 where
    style_att s =  Style_Att_30 (s2b_escape s)
    style_att_bs =  Style_Att_30 
instance A_Style Att29 where
    style_att s =  Style_Att_29 (s2b_escape s)
    style_att_bs =  Style_Att_29 
instance A_Style Att27 where
    style_att s =  Style_Att_27 (s2b_escape s)
    style_att_bs =  Style_Att_27 
instance A_Style Att26 where
    style_att s =  Style_Att_26 (s2b_escape s)
    style_att_bs =  Style_Att_26 
instance A_Style Att24 where
    style_att s =  Style_Att_24 (s2b_escape s)
    style_att_bs =  Style_Att_24 
instance A_Style Att21 where
    style_att s =  Style_Att_21 (s2b_escape s)
    style_att_bs =  Style_Att_21 
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 Att16 where
    style_att s =  Style_Att_16 (s2b_escape s)
    style_att_bs =  Style_Att_16 
instance A_Style Att15 where
    style_att s =  Style_Att_15 (s2b_escape s)
    style_att_bs =  Style_Att_15 
instance A_Style Att14 where
    style_att s =  Style_Att_14 (s2b_escape s)
    style_att_bs =  Style_Att_14 
instance A_Style Att13 where
    style_att s =  Style_Att_13 (s2b_escape s)
    style_att_bs =  Style_Att_13 
instance A_Style Att12 where
    style_att s =  Style_Att_12 (s2b_escape s)
    style_att_bs =  Style_Att_12 
instance A_Style Att11 where
    style_att s =  Style_Att_11 (s2b_escape s)
    style_att_bs =  Style_Att_11 
instance A_Style Att7 where
    style_att s =  Style_Att_7 (s2b_escape s)
    style_att_bs =  Style_Att_7 

class A_Height a where
    height_att :: String -> a
    height_att_bs :: B.ByteString -> a
instance A_Height Att21 where
    height_att s =  Height_Att_21 (s2b_escape s)
    height_att_bs =  Height_Att_21 
instance A_Height Att19 where
    height_att s =  Height_Att_19 (s2b_escape s)
    height_att_bs =  Height_Att_19 

class A_Codetype a where
    codetype_att :: String -> a
    codetype_att_bs :: B.ByteString -> a
instance A_Codetype Att19 where
    codetype_att s =  Codetype_Att_19 (s2b_escape s)
    codetype_att_bs =  Codetype_Att_19 

class A_Char a where
    char_att :: String -> a
    char_att_bs :: B.ByteString -> a
instance A_Char Att43 where
    char_att s =  Char_Att_43 (s2b_escape s)
    char_att_bs =  Char_Att_43 
instance A_Char Att42 where
    char_att s =  Char_Att_42 (s2b_escape s)
    char_att_bs =  Char_Att_42 
instance A_Char Att41 where
    char_att s =  Char_Att_41 (s2b_escape s)
    char_att_bs =  Char_Att_41 

class A_Multiple a where
    multiple_att :: String -> a
instance A_Multiple Att31 where
    multiple_att s =  Multiple_Att_31 (s2b (show s))

class A_Codebase a where
    codebase_att :: String -> a
    codebase_att_bs :: B.ByteString -> a
instance A_Codebase Att19 where
    codebase_att s =  Codebase_Att_19 (s2b_escape s)
    codebase_att_bs =  Codebase_Att_19 

class A_Xmlns a where
    xmlns_att :: String -> a
    xmlns_att_bs :: B.ByteString -> a
instance A_Xmlns Att0 where
    xmlns_att s =  Xmlns_Att_0 (s2b_escape s)
    xmlns_att_bs =  Xmlns_Att_0 

class A_Profile a where
    profile_att :: String -> a
    profile_att_bs :: B.ByteString -> a
instance A_Profile Att1 where
    profile_att s =  Profile_Att_1 (s2b_escape s)
    profile_att_bs =  Profile_Att_1 

class A_Rel a where
    rel_att :: String -> a
    rel_att_bs :: B.ByteString -> a
instance A_Rel Att15 where
    rel_att s =  Rel_Att_15 (s2b_escape s)
    rel_att_bs =  Rel_Att_15 
instance A_Rel Att7 where
    rel_att s =  Rel_Att_7 (s2b_escape s)
    rel_att_bs =  Rel_Att_7 

class A_Onsubmit a where
    onsubmit_att :: String -> a
    onsubmit_att_bs :: B.ByteString -> a
instance A_Onsubmit Att27 where
    onsubmit_att s =  Onsubmit_Att_27 (s2b_escape s)
    onsubmit_att_bs =  Onsubmit_Att_27 

class A_Ondblclick a where
    ondblclick_att :: String -> a
    ondblclick_att_bs :: B.ByteString -> a
instance A_Ondblclick Att43 where
    ondblclick_att s =  Ondblclick_Att_43 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_43 
instance A_Ondblclick Att42 where
    ondblclick_att s =  Ondblclick_Att_42 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_42 
instance A_Ondblclick Att41 where
    ondblclick_att s =  Ondblclick_Att_41 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_41 
instance A_Ondblclick Att40 where
    ondblclick_att s =  Ondblclick_Att_40 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_40 
instance A_Ondblclick Att39 where
    ondblclick_att s =  Ondblclick_Att_39 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_39 
instance A_Ondblclick Att38 where
    ondblclick_att s =  Ondblclick_Att_38 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_38 
instance A_Ondblclick Att35 where
    ondblclick_att s =  Ondblclick_Att_35 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_35 
instance A_Ondblclick Att34 where
    ondblclick_att s =  Ondblclick_Att_34 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_34 
instance A_Ondblclick Att32 where
    ondblclick_att s =  Ondblclick_Att_32 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_32 
instance A_Ondblclick Att31 where
    ondblclick_att s =  Ondblclick_Att_31 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_31 
instance A_Ondblclick Att30 where
    ondblclick_att s =  Ondblclick_Att_30 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_30 
instance A_Ondblclick Att29 where
    ondblclick_att s =  Ondblclick_Att_29 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_29 
instance A_Ondblclick Att27 where
    ondblclick_att s =  Ondblclick_Att_27 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_27 
instance A_Ondblclick Att26 where
    ondblclick_att s =  Ondblclick_Att_26 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_26 
instance A_Ondblclick Att24 where
    ondblclick_att s =  Ondblclick_Att_24 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_24 
instance A_Ondblclick Att21 where
    ondblclick_att s =  Ondblclick_Att_21 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_21 
instance A_Ondblclick Att19 where
    ondblclick_att s =  Ondblclick_Att_19 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_19 
instance A_Ondblclick Att16 where
    ondblclick_att s =  Ondblclick_Att_16 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_16 
instance A_Ondblclick Att15 where
    ondblclick_att s =  Ondblclick_Att_15 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_15 
instance A_Ondblclick Att14 where
    ondblclick_att s =  Ondblclick_Att_14 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_14 
instance A_Ondblclick Att13 where
    ondblclick_att s =  Ondblclick_Att_13 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_13 
instance A_Ondblclick Att12 where
    ondblclick_att s =  Ondblclick_Att_12 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_12 
instance A_Ondblclick Att11 where
    ondblclick_att s =  Ondblclick_Att_11 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_11 
instance A_Ondblclick Att7 where
    ondblclick_att s =  Ondblclick_Att_7 (s2b_escape s)
    ondblclick_att_bs =  Ondblclick_Att_7 

class A_Axis a where
    axis_att :: String -> a
    axis_att_bs :: B.ByteString -> a
instance A_Axis Att43 where
    axis_att s =  Axis_Att_43 (s2b_escape s)
    axis_att_bs =  Axis_Att_43 

class A_Cols a where
    cols_att :: String -> a
    cols_att_bs :: B.ByteString -> a
instance A_Cols Att37 where
    cols_att s =  Cols_Att_37 (s2b_escape s)
    cols_att_bs =  Cols_Att_37 
instance A_Cols Att35 where
    cols_att s =  Cols_Att_35 (s2b_escape s)
    cols_att_bs =  Cols_Att_35 

class A_Abbr a where
    abbr_att :: String -> a
    abbr_att_bs :: B.ByteString -> a
instance A_Abbr Att43 where
    abbr_att s =  Abbr_Att_43 (s2b_escape s)
    abbr_att_bs =  Abbr_Att_43 

class A_Onchange a where
    onchange_att :: String -> a
    onchange_att_bs :: B.ByteString -> a
instance A_Onchange Att35 where
    onchange_att s =  Onchange_Att_35 (s2b_escape s)
    onchange_att_bs =  Onchange_Att_35 
instance A_Onchange Att31 where
    onchange_att s =  Onchange_Att_31 (s2b_escape s)
    onchange_att_bs =  Onchange_Att_31 
instance A_Onchange Att30 where
    onchange_att s =  Onchange_Att_30 (s2b_escape s)
    onchange_att_bs =  Onchange_Att_30 

class A_Readonly a where
    readonly_att :: String -> a
instance A_Readonly Att35 where
    readonly_att s =  Readonly_Att_35 (s2b (show s))
instance A_Readonly Att30 where
    readonly_att s =  Readonly_Att_30 (s2b (show s))

class A_Href a where
    href_att :: String -> a
    href_att_bs :: B.ByteString -> a
instance A_Href Att26 where
    href_att s =  Href_Att_26 (s2b_escape s)
    href_att_bs =  Href_Att_26 
instance A_Href Att15 where
    href_att s =  Href_Att_15 (s2b_escape s)
    href_att_bs =  Href_Att_15 
instance A_Href Att7 where
    href_att s =  Href_Att_7 (s2b_escape s)
    href_att_bs =  Href_Att_7 
instance A_Href Att4 where
    href_att s =  Href_Att_4 (s2b_escape s)
    href_att_bs =  Href_Att_4 
instance A_Href Att3 where
    href_att s =  Href_Att_3 (s2b_escape s)
    href_att_bs =  Href_Att_3 

class A_Media a where
    media_att :: String -> a
    media_att_bs :: B.ByteString -> a
instance A_Media Att8 where
    media_att s =  Media_Att_8 (s2b_escape s)
    media_att_bs =  Media_Att_8 
instance A_Media Att7 where
    media_att s =  Media_Att_7 (s2b_escape s)
    media_att_bs =  Media_Att_7 

class A_Id a where
    id_att :: String -> a
    id_att_bs :: B.ByteString -> a
instance A_Id Att43 where
    id_att s =  Id_Att_43 (s2b_escape s)
    id_att_bs =  Id_Att_43 
instance A_Id Att42 where
    id_att s =  Id_Att_42 (s2b_escape s)
    id_att_bs =  Id_Att_42 
instance A_Id Att41 where
    id_att s =  Id_Att_41 (s2b_escape s)
    id_att_bs =  Id_Att_41 
instance A_Id Att40 where
    id_att s =  Id_Att_40 (s2b_escape s)
    id_att_bs =  Id_Att_40 
instance A_Id Att39 where
    id_att s =  Id_Att_39 (s2b_escape s)
    id_att_bs =  Id_Att_39 
instance A_Id Att38 where
    id_att s =  Id_Att_38 (s2b_escape s)
    id_att_bs =  Id_Att_38 
instance A_Id Att35 where
    id_att s =  Id_Att_35 (s2b_escape s)
    id_att_bs =  Id_Att_35 
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 Att29 where
    id_att s =  Id_Att_29 (s2b_escape s)
    id_att_bs =  Id_Att_29 
instance A_Id Att27 where
    id_att s =  Id_Att_27 (s2b_escape s)
    id_att_bs =  Id_Att_27 
instance A_Id Att26 where
    id_att s =  Id_Att_26 (s2b_escape s)
    id_att_bs =  Id_Att_26 
instance A_Id Att25 where
    id_att s =  Id_Att_25 (s2b_escape s)
    id_att_bs =  Id_Att_25 
instance A_Id Att24 where
    id_att s =  Id_Att_24 (s2b_escape s)
    id_att_bs =  Id_Att_24 
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 Att16 where
    id_att s =  Id_Att_16 (s2b_escape s)
    id_att_bs =  Id_Att_16 
instance A_Id Att15 where
    id_att s =  Id_Att_15 (s2b_escape s)
    id_att_bs =  Id_Att_15 
instance A_Id Att14 where
    id_att s =  Id_Att_14 (s2b_escape s)
    id_att_bs =  Id_Att_14 
instance A_Id Att13 where
    id_att s =  Id_Att_13 (s2b_escape s)
    id_att_bs =  Id_Att_13 
instance A_Id Att12 where
    id_att s =  Id_Att_12 (s2b_escape s)
    id_att_bs =  Id_Att_12 
instance A_Id Att11 where
    id_att s =  Id_Att_11 (s2b_escape s)
    id_att_bs =  Id_Att_11 
instance A_Id Att10 where
    id_att s =  Id_Att_10 (s2b_escape s)
    id_att_bs =  Id_Att_10 
instance A_Id Att8 where
    id_att s =  Id_Att_8 (s2b_escape s)
    id_att_bs =  Id_Att_8 
instance A_Id Att7 where
    id_att s =  Id_Att_7 (s2b_escape s)
    id_att_bs =  Id_Att_7 
instance A_Id Att5 where
    id_att s =  Id_Att_5 (s2b_escape s)
    id_att_bs =  Id_Att_5 
instance A_Id Att3 where
    id_att s =  Id_Att_3 (s2b_escape s)
    id_att_bs =  Id_Att_3 
instance A_Id Att2 where
    id_att s =  Id_Att_2 (s2b_escape s)
    id_att_bs =  Id_Att_2 
instance A_Id Att1 where
    id_att s =  Id_Att_1 (s2b_escape s)
    id_att_bs =  Id_Att_1 
instance A_Id Att0 where
    id_att s =  Id_Att_0 (s2b_escape s)
    id_att_bs =  Id_Att_0 

class A_Src a where
    src_att :: String -> a
    src_att_bs :: B.ByteString -> a
instance A_Src Att30 where
    src_att s =  Src_Att_30 (s2b_escape s)
    src_att_bs =  Src_Att_30 
instance A_Src Att22 where
    src_att s =  Src_Att_22 (s2b_escape s)
    src_att_bs =  Src_Att_22 
instance A_Src Att21 where
    src_att s =  Src_Att_21 (s2b_escape s)
    src_att_bs =  Src_Att_21 
instance A_Src Att10 where
    src_att s =  Src_Att_10 (s2b_escape s)
    src_att_bs =  Src_Att_10 

class A_Value a where
    value_att :: String -> a
    value_att_bs :: B.ByteString -> a
instance A_Value Att39 where
    value_att s =  Value_Att_39 (s2b_escape s)
    value_att_bs =  Value_Att_39 
instance A_Value Att34 where
    value_att s =  Value_Att_34 (s2b_escape s)
    value_att_bs =  Value_Att_34 
instance A_Value Att30 where
    value_att s =  Value_Att_30 (s2b_escape s)
    value_att_bs =  Value_Att_30 
instance A_Value Att20 where
    value_att s =  Value_Att_20 (s2b_escape s)
    value_att_bs =  Value_Att_20 

class A_For a where
    for_att :: String -> a
    for_att_bs :: B.ByteString -> a
instance A_For Att29 where
    for_att s =  For_Att_29 (s2b_escape s)
    for_att_bs =  For_Att_29 

class A_Data a where
    data_att :: String -> a
    data_att_bs :: B.ByteString -> a
instance A_Data Att19 where
    data_att s =  Data_Att_19 (s2b_escape s)
    data_att_bs =  Data_Att_19 

class A_Hreflang a where
    hreflang_att :: String -> a
    hreflang_att_bs :: B.ByteString -> a
instance A_Hreflang Att15 where
    hreflang_att s =  Hreflang_Att_15 (s2b_escape s)
    hreflang_att_bs =  Hreflang_Att_15 
instance A_Hreflang Att7 where
    hreflang_att s =  Hreflang_Att_7 (s2b_escape s)
    hreflang_att_bs =  Hreflang_Att_7 

class A_Checked a where
    checked_att :: String -> a
instance A_Checked Att30 where
    checked_att s =  Checked_Att_30 (s2b (show s))

class A_Declare a where
    declare_att :: String -> a
instance A_Declare Att19 where
    declare_att s =  Declare_Att_19 (s2b (show s))

class A_Onkeypress a where
    onkeypress_att :: String -> a
    onkeypress_att_bs :: B.ByteString -> a
instance A_Onkeypress Att43 where
    onkeypress_att s =  Onkeypress_Att_43 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_43 
instance A_Onkeypress Att42 where
    onkeypress_att s =  Onkeypress_Att_42 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_42 
instance A_Onkeypress Att41 where
    onkeypress_att s =  Onkeypress_Att_41 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_41 
instance A_Onkeypress Att40 where
    onkeypress_att s =  Onkeypress_Att_40 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_40 
instance A_Onkeypress Att39 where
    onkeypress_att s =  Onkeypress_Att_39 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_39 
instance A_Onkeypress Att38 where
    onkeypress_att s =  Onkeypress_Att_38 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_38 
instance A_Onkeypress Att35 where
    onkeypress_att s =  Onkeypress_Att_35 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_35 
instance A_Onkeypress Att34 where
    onkeypress_att s =  Onkeypress_Att_34 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_34 
instance A_Onkeypress Att32 where
    onkeypress_att s =  Onkeypress_Att_32 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_32 
instance A_Onkeypress Att31 where
    onkeypress_att s =  Onkeypress_Att_31 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_31 
instance A_Onkeypress Att30 where
    onkeypress_att s =  Onkeypress_Att_30 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_30 
instance A_Onkeypress Att29 where
    onkeypress_att s =  Onkeypress_Att_29 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_29 
instance A_Onkeypress Att27 where
    onkeypress_att s =  Onkeypress_Att_27 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_27 
instance A_Onkeypress Att26 where
    onkeypress_att s =  Onkeypress_Att_26 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_26 
instance A_Onkeypress Att24 where
    onkeypress_att s =  Onkeypress_Att_24 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_24 
instance A_Onkeypress Att21 where
    onkeypress_att s =  Onkeypress_Att_21 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_21 
instance A_Onkeypress Att19 where
    onkeypress_att s =  Onkeypress_Att_19 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_19 
instance A_Onkeypress Att16 where
    onkeypress_att s =  Onkeypress_Att_16 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_16 
instance A_Onkeypress Att15 where
    onkeypress_att s =  Onkeypress_Att_15 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_15 
instance A_Onkeypress Att14 where
    onkeypress_att s =  Onkeypress_Att_14 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_14 
instance A_Onkeypress Att13 where
    onkeypress_att s =  Onkeypress_Att_13 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_13 
instance A_Onkeypress Att12 where
    onkeypress_att s =  Onkeypress_Att_12 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_12 
instance A_Onkeypress Att11 where
    onkeypress_att s =  Onkeypress_Att_11 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_11 
instance A_Onkeypress Att7 where
    onkeypress_att s =  Onkeypress_Att_7 (s2b_escape s)
    onkeypress_att_bs =  Onkeypress_Att_7 

class A_Label a where
    label_att :: String -> a
    label_att_bs :: B.ByteString -> a
instance A_Label Att34 where
    label_att s =  Label_Att_34 (s2b_escape s)
    label_att_bs =  Label_Att_34 
instance A_Label Att33 where
    label_att s =  Label_Att_33 (s2b_escape s)
    label_att_bs =  Label_Att_33 
instance A_Label Att32 where
    label_att s =  Label_Att_32 (s2b_escape s)
    label_att_bs =  Label_Att_32 

class A_Class a where
    class_att :: String -> a
    class_att_bs :: B.ByteString -> a
instance A_Class Att43 where
    class_att s =  Class_Att_43 (s2b_escape s)
    class_att_bs =  Class_Att_43 
instance A_Class Att42 where
    class_att s =  Class_Att_42 (s2b_escape s)
    class_att_bs =  Class_Att_42 
instance A_Class Att41 where
    class_att s =  Class_Att_41 (s2b_escape s)
    class_att_bs =  Class_Att_41 
instance A_Class Att40 where
    class_att s =  Class_Att_40 (s2b_escape s)
    class_att_bs =  Class_Att_40 
instance A_Class Att39 where
    class_att s =  Class_Att_39 (s2b_escape s)
    class_att_bs =  Class_Att_39 
instance A_Class Att38 where
    class_att s =  Class_Att_38 (s2b_escape s)
    class_att_bs =  Class_Att_38 
instance A_Class Att35 where
    class_att s =  Class_Att_35 (s2b_escape s)
    class_att_bs =  Class_Att_35 
instance A_Class Att34 where
    class_att s =  Class_Att_34 (s2b_escape s)
    class_att_bs =  Class_Att_34 
instance A_Class Att32 where
    class_att s =  Class_Att_32 (s2b_escape s)
    class_att_bs =  Class_Att_32 
instance A_Class Att31 where
    class_att s =  Class_Att_31 (s2b_escape s)
    class_att_bs =  Class_Att_31 
instance A_Class Att30 where
    class_att s =  Class_Att_30 (s2b_escape s)
    class_att_bs =  Class_Att_30 
instance A_Class Att29 where
    class_att s =  Class_Att_29 (s2b_escape s)
    class_att_bs =  Class_Att_29 
instance A_Class Att27 where
    class_att s =  Class_Att_27 (s2b_escape s)
    class_att_bs =  Class_Att_27 
instance A_Class Att26 where
    class_att s =  Class_Att_26 (s2b_escape s)
    class_att_bs =  Class_Att_26 
instance A_Class Att24 where
    class_att s =  Class_Att_24 (s2b_escape s)
    class_att_bs =  Class_Att_24 
instance A_Class Att21 where
    class_att s =  Class_Att_21 (s2b_escape s)
    class_att_bs =  Class_Att_21 
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 Att16 where
    class_att s =  Class_Att_16 (s2b_escape s)
    class_att_bs =  Class_Att_16 
instance A_Class Att15 where
    class_att s =  Class_Att_15 (s2b_escape s)
    class_att_bs =  Class_Att_15 
instance A_Class Att14 where
    class_att s =  Class_Att_14 (s2b_escape s)
    class_att_bs =  Class_Att_14 
instance A_Class Att13 where
    class_att s =  Class_Att_13 (s2b_escape s)
    class_att_bs =  Class_Att_13 
instance A_Class Att12 where
    class_att s =  Class_Att_12 (s2b_escape s)
    class_att_bs =  Class_Att_12 
instance A_Class Att11 where
    class_att s =  Class_Att_11 (s2b_escape s)
    class_att_bs =  Class_Att_11 
instance A_Class Att7 where
    class_att s =  Class_Att_7 (s2b_escape s)
    class_att_bs =  Class_Att_7 

class A_Type a where
    type_att :: String -> a
    type_att_bs :: B.ByteString -> a
instance A_Type Att39 where
    type_att s =  Type_Att_39 (s2b_escape s)
    type_att_bs =  Type_Att_39 
instance A_Type Att30 where
    type_att s =  Type_Att_30 (s2b_escape s)
    type_att_bs =  Type_Att_30 
instance A_Type Att20 where
    type_att s =  Type_Att_20 (s2b_escape s)
    type_att_bs =  Type_Att_20 
instance A_Type Att19 where
    type_att s =  Type_Att_19 (s2b_escape s)
    type_att_bs =  Type_Att_19 
instance A_Type Att15 where
    type_att s =  Type_Att_15 (s2b_escape s)
    type_att_bs =  Type_Att_15 
instance A_Type Att10 where
    type_att s =  Type_Att_10 (s2b_escape s)
    type_att_bs =  Type_Att_10 
instance A_Type Att9 where
    type_att s =  Type_Att_9 (s2b_escape s)
    type_att_bs =  Type_Att_9 
instance A_Type Att8 where
    type_att s =  Type_Att_8 (s2b_escape s)
    type_att_bs =  Type_Att_8 
instance A_Type Att7 where
    type_att s =  Type_Att_7 (s2b_escape s)
    type_att_bs =  Type_Att_7 

class A_Shape a where
    shape_att :: ShapeEnum -> a
instance A_Shape Att26 where
    shape_att s =  Shape_Att_26 (s2b (show s))
instance A_Shape Att15 where
    shape_att s =  Shape_Att_15 (s2b (show s))

class A_Accesskey a where
    accesskey_att :: String -> a
    accesskey_att_bs :: B.ByteString -> a
instance A_Accesskey Att39 where
    accesskey_att s =  Accesskey_Att_39 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_39 
instance A_Accesskey Att38 where
    accesskey_att s =  Accesskey_Att_38 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_38 
instance A_Accesskey Att35 where
    accesskey_att s =  Accesskey_Att_35 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_35 
instance A_Accesskey Att30 where
    accesskey_att s =  Accesskey_Att_30 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_30 
instance A_Accesskey Att29 where
    accesskey_att s =  Accesskey_Att_29 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_29 
instance A_Accesskey Att26 where
    accesskey_att s =  Accesskey_Att_26 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_26 
instance A_Accesskey Att15 where
    accesskey_att s =  Accesskey_Att_15 (s2b_escape s)
    accesskey_att_bs =  Accesskey_Att_15 

class A_Headers a where
    headers_att :: String -> a
    headers_att_bs :: B.ByteString -> a
instance A_Headers Att43 where
    headers_att s =  Headers_Att_43 (s2b_escape s)
    headers_att_bs =  Headers_Att_43 

class A_Disabled a where
    disabled_att :: String -> a
instance A_Disabled Att39 where
    disabled_att s =  Disabled_Att_39 (s2b (show s))
instance A_Disabled Att35 where
    disabled_att s =  Disabled_Att_35 (s2b (show s))
instance A_Disabled Att34 where
    disabled_att s =  Disabled_Att_34 (s2b (show s))
instance A_Disabled Att32 where
    disabled_att s =  Disabled_Att_32 (s2b (show s))
instance A_Disabled Att31 where
    disabled_att s =  Disabled_Att_31 (s2b (show s))
instance A_Disabled Att30 where
    disabled_att s =  Disabled_Att_30 (s2b (show s))

class A_Rules a where
    rules_att :: RulesEnum -> a
instance A_Rules Att40 where
    rules_att s =  Rules_Att_40 (s2b (show s))

class A_Rows a where
    rows_att :: String -> a
    rows_att_bs :: B.ByteString -> a
instance A_Rows Att36 where
    rows_att s =  Rows_Att_36 (s2b_escape s)
    rows_att_bs =  Rows_Att_36 
instance A_Rows Att35 where
    rows_att s =  Rows_Att_35 (s2b_escape s)
    rows_att_bs =  Rows_Att_35 

class A_Onfocus a where
    onfocus_att :: String -> a
    onfocus_att_bs :: B.ByteString -> a
instance A_Onfocus Att39 where
    onfocus_att s =  Onfocus_Att_39 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_39 
instance A_Onfocus Att35 where
    onfocus_att s =  Onfocus_Att_35 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_35 
instance A_Onfocus Att31 where
    onfocus_att s =  Onfocus_Att_31 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_31 
instance A_Onfocus Att30 where
    onfocus_att s =  Onfocus_Att_30 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_30 
instance A_Onfocus Att29 where
    onfocus_att s =  Onfocus_Att_29 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_29 
instance A_Onfocus Att26 where
    onfocus_att s =  Onfocus_Att_26 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_26 
instance A_Onfocus Att15 where
    onfocus_att s =  Onfocus_Att_15 (s2b_escape s)
    onfocus_att_bs =  Onfocus_Att_15 

class A_Colspan a where
    colspan_att :: String -> a
    colspan_att_bs :: B.ByteString -> a
instance A_Colspan Att43 where
    colspan_att s =  Colspan_Att_43 (s2b_escape s)
    colspan_att_bs =  Colspan_Att_43 

class A_Rowspan a where
    rowspan_att :: String -> a
    rowspan_att_bs :: B.ByteString -> a
instance A_Rowspan Att43 where
    rowspan_att s =  Rowspan_Att_43 (s2b_escape s)
    rowspan_att_bs =  Rowspan_Att_43 

class A_Defer a where
    defer_att :: String -> a
instance A_Defer Att10 where
    defer_att s =  Defer_Att_10 (s2b (show s))

class A_Cellspacing a where
    cellspacing_att :: String -> a
    cellspacing_att_bs :: B.ByteString -> a
instance A_Cellspacing Att40 where
    cellspacing_att s =  Cellspacing_Att_40 (s2b_escape s)
    cellspacing_att_bs =  Cellspacing_Att_40 

class A_Charoff a where
    charoff_att :: String -> a
    charoff_att_bs :: B.ByteString -> a
instance A_Charoff Att43 where
    charoff_att s =  Charoff_Att_43 (s2b_escape s)
    charoff_att_bs =  Charoff_Att_43 
instance A_Charoff Att42 where
    charoff_att s =  Charoff_Att_42 (s2b_escape s)
    charoff_att_bs =  Charoff_Att_42 
instance A_Charoff Att41 where
    charoff_att s =  Charoff_Att_41 (s2b_escape s)
    charoff_att_bs =  Charoff_Att_41 

class A_Cite a where
    cite_att :: String -> a
    cite_att_bs :: B.ByteString -> a
instance A_Cite Att14 where
    cite_att s =  Cite_Att_14 (s2b_escape s)
    cite_att_bs =  Cite_Att_14 
instance A_Cite Att13 where
    cite_att s =  Cite_Att_13 (s2b_escape s)
    cite_att_bs =  Cite_Att_13 

class A_Maxlength a where
    maxlength_att :: String -> a
    maxlength_att_bs :: B.ByteString -> a
instance A_Maxlength Att30 where
    maxlength_att s =  Maxlength_Att_30 (s2b_escape s)
    maxlength_att_bs =  Maxlength_Att_30 

class A_Onselect a where
    onselect_att :: String -> a
    onselect_att_bs :: B.ByteString -> a
instance A_Onselect Att35 where
    onselect_att s =  Onselect_Att_35 (s2b_escape s)
    onselect_att_bs =  Onselect_Att_35 
instance A_Onselect Att30 where
    onselect_att s =  Onselect_Att_30 (s2b_escape s)
    onselect_att_bs =  Onselect_Att_30 

class A_Archive a where
    archive_att :: String -> a
    archive_att_bs :: B.ByteString -> a
instance A_Archive Att19 where
    archive_att s =  Archive_Att_19 (s2b_escape s)
    archive_att_bs =  Archive_Att_19 

class A_Alt a where
    alt_att :: String -> a
    alt_att_bs :: B.ByteString -> a
instance A_Alt Att30 where
    alt_att s =  Alt_Att_30 (s2b_escape s)
    alt_att_bs =  Alt_Att_30 
instance A_Alt Att26 where
    alt_att s =  Alt_Att_26 (s2b_escape s)
    alt_att_bs =  Alt_Att_26 
instance A_Alt Att23 where
    alt_att s =  Alt_Att_23 (s2b_escape s)
    alt_att_bs =  Alt_Att_23 
instance A_Alt Att21 where
    alt_att s =  Alt_Att_21 (s2b_escape s)
    alt_att_bs =  Alt_Att_21 

class A_Accept a where
    accept_att :: String -> a
    accept_att_bs :: B.ByteString -> a
instance A_Accept Att30 where
    accept_att s =  Accept_Att_30 (s2b_escape s)
    accept_att_bs =  Accept_Att_30 
instance A_Accept Att27 where
    accept_att s =  Accept_Att_27 (s2b_escape s)
    accept_att_bs =  Accept_Att_27 

class A_Classid a where
    classid_att :: String -> a
    classid_att_bs :: B.ByteString -> a
instance A_Classid Att19 where
    classid_att s =  Classid_Att_19 (s2b_escape s)
    classid_att_bs =  Classid_Att_19 

class A_Longdesc a where
    longdesc_att :: String -> a
    longdesc_att_bs :: B.ByteString -> a
instance A_Longdesc Att21 where
    longdesc_att s =  Longdesc_Att_21 (s2b_escape s)
    longdesc_att_bs =  Longdesc_Att_21 

class A_Onmouseout a where
    onmouseout_att :: String -> a
    onmouseout_att_bs :: B.ByteString -> a
instance A_Onmouseout Att43 where
    onmouseout_att s =  Onmouseout_Att_43 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_43 
instance A_Onmouseout Att42 where
    onmouseout_att s =  Onmouseout_Att_42 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_42 
instance A_Onmouseout Att41 where
    onmouseout_att s =  Onmouseout_Att_41 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_41 
instance A_Onmouseout Att40 where
    onmouseout_att s =  Onmouseout_Att_40 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_40 
instance A_Onmouseout Att39 where
    onmouseout_att s =  Onmouseout_Att_39 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_39 
instance A_Onmouseout Att38 where
    onmouseout_att s =  Onmouseout_Att_38 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_38 
instance A_Onmouseout Att35 where
    onmouseout_att s =  Onmouseout_Att_35 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_35 
instance A_Onmouseout Att34 where
    onmouseout_att s =  Onmouseout_Att_34 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_34 
instance A_Onmouseout Att32 where
    onmouseout_att s =  Onmouseout_Att_32 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_32 
instance A_Onmouseout Att31 where
    onmouseout_att s =  Onmouseout_Att_31 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_31 
instance A_Onmouseout Att30 where
    onmouseout_att s =  Onmouseout_Att_30 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_30 
instance A_Onmouseout Att29 where
    onmouseout_att s =  Onmouseout_Att_29 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_29 
instance A_Onmouseout Att27 where
    onmouseout_att s =  Onmouseout_Att_27 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_27 
instance A_Onmouseout Att26 where
    onmouseout_att s =  Onmouseout_Att_26 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_26 
instance A_Onmouseout Att24 where
    onmouseout_att s =  Onmouseout_Att_24 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_24 
instance A_Onmouseout Att21 where
    onmouseout_att s =  Onmouseout_Att_21 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_21 
instance A_Onmouseout Att19 where
    onmouseout_att s =  Onmouseout_Att_19 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_19 
instance A_Onmouseout Att16 where
    onmouseout_att s =  Onmouseout_Att_16 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_16 
instance A_Onmouseout Att15 where
    onmouseout_att s =  Onmouseout_Att_15 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_15 
instance A_Onmouseout Att14 where
    onmouseout_att s =  Onmouseout_Att_14 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_14 
instance A_Onmouseout Att13 where
    onmouseout_att s =  Onmouseout_Att_13 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_13 
instance A_Onmouseout Att12 where
    onmouseout_att s =  Onmouseout_Att_12 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_12 
instance A_Onmouseout Att11 where
    onmouseout_att s =  Onmouseout_Att_11 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_11 
instance A_Onmouseout Att7 where
    onmouseout_att s =  Onmouseout_Att_7 (s2b_escape s)
    onmouseout_att_bs =  Onmouseout_Att_7 

class A_Border a where
    border_att :: String -> a
    border_att_bs :: B.ByteString -> a
instance A_Border Att40 where
    border_att s =  Border_Att_40 (s2b_escape s)
    border_att_bs =  Border_Att_40 

class A_Onunload a where
    onunload_att :: String -> a
    onunload_att_bs :: B.ByteString -> a
instance A_Onunload Att12 where
    onunload_att s =  Onunload_Att_12 (s2b_escape s)
    onunload_att_bs =  Onunload_Att_12 

class A_Onload a where
    onload_att :: String -> a
    onload_att_bs :: B.ByteString -> a
instance A_Onload Att12 where
    onload_att s =  Onload_Att_12 (s2b_escape s)
    onload_att_bs =  Onload_Att_12 

class A_Action a where
    action_att :: String -> a
    action_att_bs :: B.ByteString -> a
instance A_Action Att28 where
    action_att s =  Action_Att_28 (s2b_escape s)
    action_att_bs =  Action_Att_28 
instance A_Action Att27 where
    action_att s =  Action_Att_27 (s2b_escape s)
    action_att_bs =  Action_Att_27 

class A_Cellpadding a where
    cellpadding_att :: String -> a
    cellpadding_att_bs :: B.ByteString -> a
instance A_Cellpadding Att40 where
    cellpadding_att s =  Cellpadding_Att_40 (s2b_escape s)
    cellpadding_att_bs =  Cellpadding_Att_40 

class A_Valuetype a where
    valuetype_att :: ValuetypeEnum -> a
instance A_Valuetype Att20 where
    valuetype_att s =  Valuetype_Att_20 (s2b (show s))

class A_Selected a where
    selected_att :: String -> a
instance A_Selected Att34 where
    selected_att s =  Selected_Att_34 (s2b (show s))

class RenderAttribute a where
    renderAtt :: a -> (B.ByteString,B.ByteString)
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 (Abbr_Att_43 b) = (abbr_byte,b)
    renderAtt (Axis_Att_43 b) = (axis_byte,b)
    renderAtt (Headers_Att_43 b) = (headers_byte,b)
    renderAtt (Scope_Att_43 b) = (scope_byte,b)
    renderAtt (Rowspan_Att_43 b) = (rowspan_byte,b)
    renderAtt (Colspan_Att_43 b) = (colspan_byte,b)
    renderAtt (Align_Att_43 b) = (align_byte,b)
    renderAtt (Char_Att_43 b) = (char_byte,b)
    renderAtt (Charoff_Att_43 b) = (charoff_byte,b)
    renderAtt (Valign_Att_43 b) = (valign_byte,b)

instance RenderAttribute Att42 where
    renderAtt (Id_Att_42 b) = (id_byte,b)
    renderAtt (Class_Att_42 b) = (class_byte,b)
    renderAtt (Style_Att_42 b) = (style_byte,b)
    renderAtt (Title_Att_42 b) = (title_byte,b)
    renderAtt (Lang_Att_42 b) = (lang_byte,b)
    renderAtt (Dir_Att_42 b) = (dir_byte,b)
    renderAtt (Onclick_Att_42 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_42 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_42 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_42 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_42 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_42 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_42 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_42 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_42 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_42 b) = (onkeyup_byte,b)
    renderAtt (Span_Att_42 b) = (span_byte,b)
    renderAtt (Width_Att_42 b) = (width_byte,b)
    renderAtt (Align_Att_42 b) = (align_byte,b)
    renderAtt (Char_Att_42 b) = (char_byte,b)
    renderAtt (Charoff_Att_42 b) = (charoff_byte,b)
    renderAtt (Valign_Att_42 b) = (valign_byte,b)

instance RenderAttribute Att41 where
    renderAtt (Id_Att_41 b) = (id_byte,b)
    renderAtt (Class_Att_41 b) = (class_byte,b)
    renderAtt (Style_Att_41 b) = (style_byte,b)
    renderAtt (Title_Att_41 b) = (title_byte,b)
    renderAtt (Lang_Att_41 b) = (lang_byte,b)
    renderAtt (Dir_Att_41 b) = (dir_byte,b)
    renderAtt (Onclick_Att_41 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_41 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_41 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_41 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_41 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_41 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_41 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_41 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_41 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_41 b) = (onkeyup_byte,b)
    renderAtt (Align_Att_41 b) = (align_byte,b)
    renderAtt (Char_Att_41 b) = (char_byte,b)
    renderAtt (Charoff_Att_41 b) = (charoff_byte,b)
    renderAtt (Valign_Att_41 b) = (valign_byte,b)

instance RenderAttribute Att40 where
    renderAtt (Id_Att_40 b) = (id_byte,b)
    renderAtt (Class_Att_40 b) = (class_byte,b)
    renderAtt (Style_Att_40 b) = (style_byte,b)
    renderAtt (Title_Att_40 b) = (title_byte,b)
    renderAtt (Lang_Att_40 b) = (lang_byte,b)
    renderAtt (Dir_Att_40 b) = (dir_byte,b)
    renderAtt (Onclick_Att_40 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_40 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_40 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_40 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_40 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_40 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_40 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_40 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_40 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_40 b) = (onkeyup_byte,b)
    renderAtt (Summary_Att_40 b) = (summary_byte,b)
    renderAtt (Width_Att_40 b) = (width_byte,b)
    renderAtt (Border_Att_40 b) = (border_byte,b)
    renderAtt (Frame_Att_40 b) = (frame_byte,b)
    renderAtt (Rules_Att_40 b) = (rules_byte,b)
    renderAtt (Cellspacing_Att_40 b) = (cellspacing_byte,b)
    renderAtt (Cellpadding_Att_40 b) = (cellpadding_byte,b)

instance RenderAttribute Att39 where
    renderAtt (Id_Att_39 b) = (id_byte,b)
    renderAtt (Class_Att_39 b) = (class_byte,b)
    renderAtt (Style_Att_39 b) = (style_byte,b)
    renderAtt (Title_Att_39 b) = (title_byte,b)
    renderAtt (Lang_Att_39 b) = (lang_byte,b)
    renderAtt (Dir_Att_39 b) = (dir_byte,b)
    renderAtt (Onclick_Att_39 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_39 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_39 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_39 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_39 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_39 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_39 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_39 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_39 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_39 b) = (onkeyup_byte,b)
    renderAtt (Accesskey_Att_39 b) = (accesskey_byte,b)
    renderAtt (Tabindex_Att_39 b) = (tabindex_byte,b)
    renderAtt (Onfocus_Att_39 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_39 b) = (onblur_byte,b)
    renderAtt (Name_Att_39 b) = (name_byte,b)
    renderAtt (Value_Att_39 b) = (value_byte,b)
    renderAtt (Type_Att_39 b) = (type_byte,b)
    renderAtt (Disabled_Att_39 b) = (disabled_byte,b)

instance RenderAttribute Att38 where
    renderAtt (Id_Att_38 b) = (id_byte,b)
    renderAtt (Class_Att_38 b) = (class_byte,b)
    renderAtt (Style_Att_38 b) = (style_byte,b)
    renderAtt (Title_Att_38 b) = (title_byte,b)
    renderAtt (Lang_Att_38 b) = (lang_byte,b)
    renderAtt (Dir_Att_38 b) = (dir_byte,b)
    renderAtt (Onclick_Att_38 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_38 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_38 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_38 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_38 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_38 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_38 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_38 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_38 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_38 b) = (onkeyup_byte,b)
    renderAtt (Accesskey_Att_38 b) = (accesskey_byte,b)

instance RenderAttribute Att37 where
    renderAtt (Cols_Att_37 b) = (cols_byte,b)

instance RenderAttribute Att36 where
    renderAtt (Rows_Att_36 b) = (rows_byte,b)

instance RenderAttribute Att35 where
    renderAtt (Id_Att_35 b) = (id_byte,b)
    renderAtt (Class_Att_35 b) = (class_byte,b)
    renderAtt (Style_Att_35 b) = (style_byte,b)
    renderAtt (Title_Att_35 b) = (title_byte,b)
    renderAtt (Lang_Att_35 b) = (lang_byte,b)
    renderAtt (Dir_Att_35 b) = (dir_byte,b)
    renderAtt (Onclick_Att_35 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_35 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_35 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_35 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_35 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_35 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_35 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_35 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_35 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_35 b) = (onkeyup_byte,b)
    renderAtt (Accesskey_Att_35 b) = (accesskey_byte,b)
    renderAtt (Tabindex_Att_35 b) = (tabindex_byte,b)
    renderAtt (Onfocus_Att_35 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_35 b) = (onblur_byte,b)
    renderAtt (Name_Att_35 b) = (name_byte,b)
    renderAtt (Rows_Att_35 b) = (rows_byte,b)
    renderAtt (Cols_Att_35 b) = (cols_byte,b)
    renderAtt (Disabled_Att_35 b) = (disabled_byte,b)
    renderAtt (Readonly_Att_35 b) = (readonly_byte,b)
    renderAtt (Onselect_Att_35 b) = (onselect_byte,b)
    renderAtt (Onchange_Att_35 b) = (onchange_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 (Lang_Att_34 b) = (lang_byte,b)
    renderAtt (Dir_Att_34 b) = (dir_byte,b)
    renderAtt (Onclick_Att_34 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_34 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_34 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_34 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_34 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_34 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_34 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_34 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_34 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_34 b) = (onkeyup_byte,b)
    renderAtt (Selected_Att_34 b) = (selected_byte,b)
    renderAtt (Disabled_Att_34 b) = (disabled_byte,b)
    renderAtt (Label_Att_34 b) = (label_byte,b)
    renderAtt (Value_Att_34 b) = (value_byte,b)

instance RenderAttribute Att33 where
    renderAtt (Label_Att_33 b) = (label_byte,b)

instance RenderAttribute Att32 where
    renderAtt (Id_Att_32 b) = (id_byte,b)
    renderAtt (Class_Att_32 b) = (class_byte,b)
    renderAtt (Style_Att_32 b) = (style_byte,b)
    renderAtt (Title_Att_32 b) = (title_byte,b)
    renderAtt (Lang_Att_32 b) = (lang_byte,b)
    renderAtt (Dir_Att_32 b) = (dir_byte,b)
    renderAtt (Onclick_Att_32 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_32 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_32 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_32 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_32 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_32 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_32 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_32 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_32 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_32 b) = (onkeyup_byte,b)
    renderAtt (Disabled_Att_32 b) = (disabled_byte,b)
    renderAtt (Label_Att_32 b) = (label_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 (Name_Att_31 b) = (name_byte,b)
    renderAtt (Size_Att_31 b) = (size_byte,b)
    renderAtt (Multiple_Att_31 b) = (multiple_byte,b)
    renderAtt (Disabled_Att_31 b) = (disabled_byte,b)
    renderAtt (Tabindex_Att_31 b) = (tabindex_byte,b)
    renderAtt (Onfocus_Att_31 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_31 b) = (onblur_byte,b)
    renderAtt (Onchange_Att_31 b) = (onchange_byte,b)

instance RenderAttribute Att30 where
    renderAtt (Id_Att_30 b) = (id_byte,b)
    renderAtt (Class_Att_30 b) = (class_byte,b)
    renderAtt (Style_Att_30 b) = (style_byte,b)
    renderAtt (Title_Att_30 b) = (title_byte,b)
    renderAtt (Lang_Att_30 b) = (lang_byte,b)
    renderAtt (Dir_Att_30 b) = (dir_byte,b)
    renderAtt (Onclick_Att_30 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_30 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_30 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_30 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_30 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_30 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_30 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_30 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_30 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_30 b) = (onkeyup_byte,b)
    renderAtt (Accesskey_Att_30 b) = (accesskey_byte,b)
    renderAtt (Tabindex_Att_30 b) = (tabindex_byte,b)
    renderAtt (Onfocus_Att_30 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_30 b) = (onblur_byte,b)
    renderAtt (Type_Att_30 b) = (type_byte,b)
    renderAtt (Name_Att_30 b) = (name_byte,b)
    renderAtt (Value_Att_30 b) = (value_byte,b)
    renderAtt (Checked_Att_30 b) = (checked_byte,b)
    renderAtt (Disabled_Att_30 b) = (disabled_byte,b)
    renderAtt (Readonly_Att_30 b) = (readonly_byte,b)
    renderAtt (Size_Att_30 b) = (size_byte,b)
    renderAtt (Maxlength_Att_30 b) = (maxlength_byte,b)
    renderAtt (Src_Att_30 b) = (src_byte,b)
    renderAtt (Alt_Att_30 b) = (alt_byte,b)
    renderAtt (Usemap_Att_30 b) = (usemap_byte,b)
    renderAtt (Onselect_Att_30 b) = (onselect_byte,b)
    renderAtt (Onchange_Att_30 b) = (onchange_byte,b)
    renderAtt (Accept_Att_30 b) = (accept_byte,b)

instance RenderAttribute Att29 where
    renderAtt (Id_Att_29 b) = (id_byte,b)
    renderAtt (Class_Att_29 b) = (class_byte,b)
    renderAtt (Style_Att_29 b) = (style_byte,b)
    renderAtt (Title_Att_29 b) = (title_byte,b)
    renderAtt (Lang_Att_29 b) = (lang_byte,b)
    renderAtt (Dir_Att_29 b) = (dir_byte,b)
    renderAtt (Onclick_Att_29 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_29 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_29 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_29 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_29 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_29 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_29 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_29 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_29 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_29 b) = (onkeyup_byte,b)
    renderAtt (For_Att_29 b) = (for_byte,b)
    renderAtt (Accesskey_Att_29 b) = (accesskey_byte,b)
    renderAtt (Onfocus_Att_29 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_29 b) = (onblur_byte,b)

instance RenderAttribute Att28 where
    renderAtt (Action_Att_28 b) = (action_byte,b)

instance RenderAttribute Att27 where
    renderAtt (Id_Att_27 b) = (id_byte,b)
    renderAtt (Class_Att_27 b) = (class_byte,b)
    renderAtt (Style_Att_27 b) = (style_byte,b)
    renderAtt (Title_Att_27 b) = (title_byte,b)
    renderAtt (Lang_Att_27 b) = (lang_byte,b)
    renderAtt (Dir_Att_27 b) = (dir_byte,b)
    renderAtt (Onclick_Att_27 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_27 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_27 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_27 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_27 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_27 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_27 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_27 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_27 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_27 b) = (onkeyup_byte,b)
    renderAtt (Action_Att_27 b) = (action_byte,b)
    renderAtt (Method_Att_27 b) = (method_byte,b)
    renderAtt (Enctype_Att_27 b) = (enctype_byte,b)
    renderAtt (Onsubmit_Att_27 b) = (onsubmit_byte,b)
    renderAtt (Onreset_Att_27 b) = (onreset_byte,b)
    renderAtt (Accept_Att_27 b) = (accept_byte,b)
    renderAtt (Accept_charset_Att_27 b) = (accept_charset_byte,b)

instance RenderAttribute Att26 where
    renderAtt (Id_Att_26 b) = (id_byte,b)
    renderAtt (Class_Att_26 b) = (class_byte,b)
    renderAtt (Style_Att_26 b) = (style_byte,b)
    renderAtt (Title_Att_26 b) = (title_byte,b)
    renderAtt (Lang_Att_26 b) = (lang_byte,b)
    renderAtt (Dir_Att_26 b) = (dir_byte,b)
    renderAtt (Onclick_Att_26 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_26 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_26 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_26 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_26 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_26 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_26 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_26 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_26 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_26 b) = (onkeyup_byte,b)
    renderAtt (Accesskey_Att_26 b) = (accesskey_byte,b)
    renderAtt (Tabindex_Att_26 b) = (tabindex_byte,b)
    renderAtt (Onfocus_Att_26 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_26 b) = (onblur_byte,b)
    renderAtt (Shape_Att_26 b) = (shape_byte,b)
    renderAtt (Coords_Att_26 b) = (coords_byte,b)
    renderAtt (Href_Att_26 b) = (href_byte,b)
    renderAtt (Nohref_Att_26 b) = (nohref_byte,b)
    renderAtt (Alt_Att_26 b) = (alt_byte,b)

instance RenderAttribute Att25 where
    renderAtt (Id_Att_25 b) = (id_byte,b)

instance RenderAttribute Att24 where
    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 (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 (Name_Att_24 b) = (name_byte,b)

instance RenderAttribute Att23 where
    renderAtt (Alt_Att_23 b) = (alt_byte,b)

instance RenderAttribute Att22 where
    renderAtt (Src_Att_22 b) = (src_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 (Src_Att_21 b) = (src_byte,b)
    renderAtt (Alt_Att_21 b) = (alt_byte,b)
    renderAtt (Longdesc_Att_21 b) = (longdesc_byte,b)
    renderAtt (Height_Att_21 b) = (height_byte,b)
    renderAtt (Width_Att_21 b) = (width_byte,b)
    renderAtt (Usemap_Att_21 b) = (usemap_byte,b)
    renderAtt (Ismap_Att_21 b) = (ismap_byte,b)

instance RenderAttribute Att20 where
    renderAtt (Id_Att_20 b) = (id_byte,b)
    renderAtt (Name_Att_20 b) = (name_byte,b)
    renderAtt (Value_Att_20 b) = (value_byte,b)
    renderAtt (Valuetype_Att_20 b) = (valuetype_byte,b)
    renderAtt (Type_Att_20 b) = (type_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 (Declare_Att_19 b) = (declare_byte,b)
    renderAtt (Classid_Att_19 b) = (classid_byte,b)
    renderAtt (Codebase_Att_19 b) = (codebase_byte,b)
    renderAtt (Data_Att_19 b) = (data_byte,b)
    renderAtt (Type_Att_19 b) = (type_byte,b)
    renderAtt (Codetype_Att_19 b) = (codetype_byte,b)
    renderAtt (Archive_Att_19 b) = (archive_byte,b)
    renderAtt (Standby_Att_19 b) = (standby_byte,b)
    renderAtt (Height_Att_19 b) = (height_byte,b)
    renderAtt (Width_Att_19 b) = (width_byte,b)
    renderAtt (Usemap_Att_19 b) = (usemap_byte,b)
    renderAtt (Name_Att_19 b) = (name_byte,b)
    renderAtt (Tabindex_Att_19 b) = (tabindex_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)

instance RenderAttribute Att17 where
    renderAtt (Dir_Att_17 b) = (dir_byte,b)

instance RenderAttribute Att16 where
    renderAtt (Id_Att_16 b) = (id_byte,b)
    renderAtt (Class_Att_16 b) = (class_byte,b)
    renderAtt (Style_Att_16 b) = (style_byte,b)
    renderAtt (Title_Att_16 b) = (title_byte,b)
    renderAtt (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 (Lang_Att_16 b) = (lang_byte,b)
    renderAtt (Dir_Att_16 b) = (dir_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 (Accesskey_Att_15 b) = (accesskey_byte,b)
    renderAtt (Tabindex_Att_15 b) = (tabindex_byte,b)
    renderAtt (Onfocus_Att_15 b) = (onfocus_byte,b)
    renderAtt (Onblur_Att_15 b) = (onblur_byte,b)
    renderAtt (Charset_Att_15 b) = (charset_byte,b)
    renderAtt (Type_Att_15 b) = (type_byte,b)
    renderAtt (Name_Att_15 b) = (name_byte,b)
    renderAtt (Href_Att_15 b) = (href_byte,b)
    renderAtt (Hreflang_Att_15 b) = (hreflang_byte,b)
    renderAtt (Rel_Att_15 b) = (rel_byte,b)
    renderAtt (Rev_Att_15 b) = (rev_byte,b)
    renderAtt (Shape_Att_15 b) = (shape_byte,b)
    renderAtt (Coords_Att_15 b) = (coords_byte,b)

instance RenderAttribute Att14 where
    renderAtt (Id_Att_14 b) = (id_byte,b)
    renderAtt (Class_Att_14 b) = (class_byte,b)
    renderAtt (Style_Att_14 b) = (style_byte,b)
    renderAtt (Title_Att_14 b) = (title_byte,b)
    renderAtt (Lang_Att_14 b) = (lang_byte,b)
    renderAtt (Dir_Att_14 b) = (dir_byte,b)
    renderAtt (Onclick_Att_14 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_14 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_14 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_14 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_14 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_14 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_14 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_14 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_14 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_14 b) = (onkeyup_byte,b)
    renderAtt (Cite_Att_14 b) = (cite_byte,b)
    renderAtt (Datetime_Att_14 b) = (datetime_byte,b)

instance RenderAttribute Att13 where
    renderAtt (Id_Att_13 b) = (id_byte,b)
    renderAtt (Class_Att_13 b) = (class_byte,b)
    renderAtt (Style_Att_13 b) = (style_byte,b)
    renderAtt (Title_Att_13 b) = (title_byte,b)
    renderAtt (Lang_Att_13 b) = (lang_byte,b)
    renderAtt (Dir_Att_13 b) = (dir_byte,b)
    renderAtt (Onclick_Att_13 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_13 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_13 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_13 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_13 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_13 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_13 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_13 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_13 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_13 b) = (onkeyup_byte,b)
    renderAtt (Cite_Att_13 b) = (cite_byte,b)

instance RenderAttribute Att12 where
    renderAtt (Id_Att_12 b) = (id_byte,b)
    renderAtt (Class_Att_12 b) = (class_byte,b)
    renderAtt (Style_Att_12 b) = (style_byte,b)
    renderAtt (Title_Att_12 b) = (title_byte,b)
    renderAtt (Lang_Att_12 b) = (lang_byte,b)
    renderAtt (Dir_Att_12 b) = (dir_byte,b)
    renderAtt (Onclick_Att_12 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_12 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_12 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_12 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_12 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_12 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_12 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_12 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_12 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_12 b) = (onkeyup_byte,b)
    renderAtt (Onload_Att_12 b) = (onload_byte,b)
    renderAtt (Onunload_Att_12 b) = (onunload_byte,b)

instance RenderAttribute Att11 where
    renderAtt (Id_Att_11 b) = (id_byte,b)
    renderAtt (Class_Att_11 b) = (class_byte,b)
    renderAtt (Style_Att_11 b) = (style_byte,b)
    renderAtt (Title_Att_11 b) = (title_byte,b)
    renderAtt (Lang_Att_11 b) = (lang_byte,b)
    renderAtt (Dir_Att_11 b) = (dir_byte,b)
    renderAtt (Onclick_Att_11 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_11 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_11 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_11 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_11 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_11 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_11 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_11 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_11 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_11 b) = (onkeyup_byte,b)

instance RenderAttribute Att10 where
    renderAtt (Id_Att_10 b) = (id_byte,b)
    renderAtt (Charset_Att_10 b) = (charset_byte,b)
    renderAtt (Type_Att_10 b) = (type_byte,b)
    renderAtt (Src_Att_10 b) = (src_byte,b)
    renderAtt (Defer_Att_10 b) = (defer_byte,b)

instance RenderAttribute Att9 where
    renderAtt (Type_Att_9 b) = (type_byte,b)

instance RenderAttribute Att8 where
    renderAtt (Lang_Att_8 b) = (lang_byte,b)
    renderAtt (Dir_Att_8 b) = (dir_byte,b)
    renderAtt (Id_Att_8 b) = (id_byte,b)
    renderAtt (Type_Att_8 b) = (type_byte,b)
    renderAtt (Media_Att_8 b) = (media_byte,b)
    renderAtt (Title_Att_8 b) = (title_byte,b)

instance RenderAttribute Att7 where
    renderAtt (Id_Att_7 b) = (id_byte,b)
    renderAtt (Class_Att_7 b) = (class_byte,b)
    renderAtt (Style_Att_7 b) = (style_byte,b)
    renderAtt (Title_Att_7 b) = (title_byte,b)
    renderAtt (Lang_Att_7 b) = (lang_byte,b)
    renderAtt (Dir_Att_7 b) = (dir_byte,b)
    renderAtt (Onclick_Att_7 b) = (onclick_byte,b)
    renderAtt (Ondblclick_Att_7 b) = (ondblclick_byte,b)
    renderAtt (Onmousedown_Att_7 b) = (onmousedown_byte,b)
    renderAtt (Onmouseup_Att_7 b) = (onmouseup_byte,b)
    renderAtt (Onmouseover_Att_7 b) = (onmouseover_byte,b)
    renderAtt (Onmousemove_Att_7 b) = (onmousemove_byte,b)
    renderAtt (Onmouseout_Att_7 b) = (onmouseout_byte,b)
    renderAtt (Onkeypress_Att_7 b) = (onkeypress_byte,b)
    renderAtt (Onkeydown_Att_7 b) = (onkeydown_byte,b)
    renderAtt (Onkeyup_Att_7 b) = (onkeyup_byte,b)
    renderAtt (Charset_Att_7 b) = (charset_byte,b)
    renderAtt (Href_Att_7 b) = (href_byte,b)
    renderAtt (Hreflang_Att_7 b) = (hreflang_byte,b)
    renderAtt (Type_Att_7 b) = (type_byte,b)
    renderAtt (Rel_Att_7 b) = (rel_byte,b)
    renderAtt (Rev_Att_7 b) = (rev_byte,b)
    renderAtt (Media_Att_7 b) = (media_byte,b)

instance RenderAttribute Att6 where
    renderAtt (Content_Att_6 b) = (content_byte,b)

instance RenderAttribute Att5 where
    renderAtt (Lang_Att_5 b) = (lang_byte,b)
    renderAtt (Dir_Att_5 b) = (dir_byte,b)
    renderAtt (Id_Att_5 b) = (id_byte,b)
    renderAtt (Http_equiv_Att_5 b) = (http_equiv_byte,b)
    renderAtt (Name_Att_5 b) = (name_byte,b)
    renderAtt (Content_Att_5 b) = (content_byte,b)
    renderAtt (Scheme_Att_5 b) = (scheme_byte,b)

instance RenderAttribute Att4 where
    renderAtt (Href_Att_4 b) = (href_byte,b)

instance RenderAttribute Att3 where
    renderAtt (Href_Att_3 b) = (href_byte,b)
    renderAtt (Id_Att_3 b) = (id_byte,b)

instance RenderAttribute Att2 where
    renderAtt (Lang_Att_2 b) = (lang_byte,b)
    renderAtt (Dir_Att_2 b) = (dir_byte,b)
    renderAtt (Id_Att_2 b) = (id_byte,b)

instance RenderAttribute Att1 where
    renderAtt (Lang_Att_1 b) = (lang_byte,b)
    renderAtt (Dir_Att_1 b) = (dir_byte,b)
    renderAtt (Id_Att_1 b) = (id_byte,b)
    renderAtt (Profile_Att_1 b) = (profile_byte,b)

instance RenderAttribute Att0 where
    renderAtt (Lang_Att_0 b) = (lang_byte,b)
    renderAtt (Dir_Att_0 b) = (dir_byte,b)
    renderAtt (Id_Att_0 b) = (id_byte,b)
    renderAtt (Xmlns_Att_0 b) = (xmlns_byte,b)

--renderAtts :: [Attributes] -> B.ByteString
sp_byte = s2b " "
eqq_byte = s2b "=\""
q_byte = s2b "\""
renderAtts [] = B.empty
renderAtts (at:[]) = B.concat [sp_byte, a, eqq_byte, b, q_byte]
   where (a,b) = renderAtt at
renderAtts at = B.concat (map (\(a,b)->B.concat [sp_byte, a, eqq_byte, b, q_byte]) (nubBy (\(a,b) (c,d)-> a==c) ats))
   where ats = map renderAtt at

data Ent0 = Head_0 [Att1]  [Ent1]  | Body_0 [Att12]  [Ent93] 
    deriving (Show)

data Ent1 = Title_1 [Att2]  [Ent2]  | Base_1 [Att3]  | Meta_1 [Att5]  | Link_1 [Att7]  | Style_1 [Att8]  [Ent2]  | Script_1 [Att10]  [Ent2]  | Object_1 [Att19]  [Ent3] 
    deriving (Show)

data Ent2 = PCDATA_2 [Att0] B.ByteString
    deriving (Show)

data Ent3 = Script_3 [Att10]  [Ent2]  | Noscript_3 [Att11]  [Ent93]  | Div_3 [Att11]  [Ent94]  | P_3 [Att11]  [Ent60]  | H1_3 [Att11]  [Ent60]  | H2_3 [Att11]  [Ent60]  | H3_3 [Att11]  [Ent60]  | H4_3 [Att11]  [Ent60]  | H5_3 [Att11]  [Ent60]  | H6_3 [Att11]  [Ent60]  | Ul_3 [Att11]  [Ent95]  | Ol_3 [Att11]  [Ent95]  | Dl_3 [Att11]  [Ent96]  | Address_3 [Att11]  [Ent60]  | Hr_3 [Att11]  | Pre_3 [Att11]  [Ent97]  | Blockquote_3 [Att13]  [Ent93]  | Ins_3 [Att14]  [Ent94]  | Del_3 [Att14]  [Ent94]  | A_3 [Att15]  [Ent4]  | Span_3 [Att11]  [Ent60]  | Bdo_3 [Att11]  [Ent60]  | Br_3 [Att18]  | Em_3 [Att11]  [Ent60]  | Strong_3 [Att11]  [Ent60]  | Dfn_3 [Att11]  [Ent60]  | Code_3 [Att11]  [Ent60]  | Samp_3 [Att11]  [Ent60]  | Kbd_3 [Att11]  [Ent60]  | Var_3 [Att11]  [Ent60]  | Cite_3 [Att11]  [Ent60]  | Abbr_3 [Att11]  [Ent60]  | Acronym_3 [Att11]  [Ent60]  | Q_3 [Att13]  [Ent60]  | Sub_3 [Att11]  [Ent60]  | Sup_3 [Att11]  [Ent60]  | Tt_3 [Att11]  [Ent60]  | I_3 [Att11]  [Ent60]  | B_3 [Att11]  [Ent60]  | Big_3 [Att11]  [Ent60]  | Small_3 [Att11]  [Ent60]  | Object_3 [Att19]  [Ent3]  | Param_3 [Att20]  | Img_3 [Att21]  | Map_3 [Att24]  [Ent61]  | Form_3 [Att27]  [Ent98]  | Label_3 [Att29]  [Ent62]  | Input_3 [Att30]  | Select_3 [Att31]  [Ent90]  | Textarea_3 [Att35]  [Ent2]  | Fieldset_3 [Att11]  [Ent133]  | Button_3 [Att39]  [Ent92]  | Table_3 [Att40]  [Ent134]  | PCDATA_3 [Att0] B.ByteString
    deriving (Show)

data Ent4 = Script_4 [Att10]  [Ent5]  | Ins_4 [Att14]  [Ent6]  | Del_4 [Att14]  [Ent6]  | Span_4 [Att11]  [Ent4]  | Bdo_4 [Att11]  [Ent4]  | Br_4 [Att18]  | Em_4 [Att11]  [Ent4]  | Strong_4 [Att11]  [Ent4]  | Dfn_4 [Att11]  [Ent4]  | Code_4 [Att11]  [Ent4]  | Samp_4 [Att11]  [Ent4]  | Kbd_4 [Att11]  [Ent4]  | Var_4 [Att11]  [Ent4]  | Cite_4 [Att11]  [Ent4]  | Abbr_4 [Att11]  [Ent4]  | Acronym_4 [Att11]  [Ent4]  | Q_4 [Att13]  [Ent4]  | Sub_4 [Att11]  [Ent4]  | Sup_4 [Att11]  [Ent4]  | Tt_4 [Att11]  [Ent4]  | I_4 [Att11]  [Ent4]  | B_4 [Att11]  [Ent4]  | Big_4 [Att11]  [Ent4]  | Small_4 [Att11]  [Ent4]  | Object_4 [Att19]  [Ent27]  | Img_4 [Att21]  | Map_4 [Att24]  [Ent28]  | Label_4 [Att29]  [Ent29]  | Input_4 [Att30]  | Select_4 [Att31]  [Ent57]  | Textarea_4 [Att35]  [Ent5]  | Button_4 [Att39]  [Ent59]  | PCDATA_4 [Att0] B.ByteString
    deriving (Show)

data Ent5 = PCDATA_5 [Att0] B.ByteString
    deriving (Show)

data Ent6 = Script_6 [Att10]  [Ent5]  | Noscript_6 [Att11]  [Ent7]  | Div_6 [Att11]  [Ent6]  | P_6 [Att11]  [Ent4]  | H1_6 [Att11]  [Ent4]  | H2_6 [Att11]  [Ent4]  | H3_6 [Att11]  [Ent4]  | H4_6 [Att11]  [Ent4]  | H5_6 [Att11]  [Ent4]  | H6_6 [Att11]  [Ent4]  | Ul_6 [Att11]  [Ent8]  | Ol_6 [Att11]  [Ent8]  | Dl_6 [Att11]  [Ent9]  | Address_6 [Att11]  [Ent4]  | Hr_6 [Att11]  | Pre_6 [Att11]  [Ent10]  | Blockquote_6 [Att13]  [Ent7]  | Ins_6 [Att14]  [Ent6]  | Del_6 [Att14]  [Ent6]  | Span_6 [Att11]  [Ent4]  | Bdo_6 [Att11]  [Ent4]  | Br_6 [Att18]  | Em_6 [Att11]  [Ent4]  | Strong_6 [Att11]  [Ent4]  | Dfn_6 [Att11]  [Ent4]  | Code_6 [Att11]  [Ent4]  | Samp_6 [Att11]  [Ent4]  | Kbd_6 [Att11]  [Ent4]  | Var_6 [Att11]  [Ent4]  | Cite_6 [Att11]  [Ent4]  | Abbr_6 [Att11]  [Ent4]  | Acronym_6 [Att11]  [Ent4]  | Q_6 [Att13]  [Ent4]  | Sub_6 [Att11]  [Ent4]  | Sup_6 [Att11]  [Ent4]  | Tt_6 [Att11]  [Ent4]  | I_6 [Att11]  [Ent4]  | B_6 [Att11]  [Ent4]  | Big_6 [Att11]  [Ent4]  | Small_6 [Att11]  [Ent4]  | Object_6 [Att19]  [Ent27]  | Img_6 [Att21]  | Map_6 [Att24]  [Ent28]  | Form_6 [Att27]  [Ent11]  | Label_6 [Att29]  [Ent29]  | Input_6 [Att30]  | Select_6 [Att31]  [Ent57]  | Textarea_6 [Att35]  [Ent5]  | Fieldset_6 [Att11]  [Ent22]  | Button_6 [Att39]  [Ent59]  | Table_6 [Att40]  [Ent23]  | PCDATA_6 [Att0] B.ByteString
    deriving (Show)

data Ent7 = Script_7 [Att10]  [Ent5]  | Noscript_7 [Att11]  [Ent7]  | Div_7 [Att11]  [Ent6]  | P_7 [Att11]  [Ent4]  | H1_7 [Att11]  [Ent4]  | H2_7 [Att11]  [Ent4]  | H3_7 [Att11]  [Ent4]  | H4_7 [Att11]  [Ent4]  | H5_7 [Att11]  [Ent4]  | H6_7 [Att11]  [Ent4]  | Ul_7 [Att11]  [Ent8]  | Ol_7 [Att11]  [Ent8]  | Dl_7 [Att11]  [Ent9]  | Address_7 [Att11]  [Ent4]  | Hr_7 [Att11]  | Pre_7 [Att11]  [Ent10]  | Blockquote_7 [Att13]  [Ent7]  | Ins_7 [Att14]  [Ent6]  | Del_7 [Att14]  [Ent6]  | Form_7 [Att27]  [Ent11]  | Fieldset_7 [Att11]  [Ent22]  | Table_7 [Att40]  [Ent23] 
    deriving (Show)

data Ent8 = Li_8 [Att11]  [Ent6] 
    deriving (Show)

data Ent9 = Dt_9 [Att11]  [Ent4]  | Dd_9 [Att11]  [Ent6] 
    deriving (Show)

data Ent10 = Script_10 [Att10]  [Ent5]  | Ins_10 [Att14]  [Ent6]  | Del_10 [Att14]  [Ent6]  | Span_10 [Att11]  [Ent4]  | Bdo_10 [Att11]  [Ent4]  | Br_10 [Att18]  | Em_10 [Att11]  [Ent4]  | Strong_10 [Att11]  [Ent4]  | Dfn_10 [Att11]  [Ent4]  | Code_10 [Att11]  [Ent4]  | Samp_10 [Att11]  [Ent4]  | Kbd_10 [Att11]  [Ent4]  | Var_10 [Att11]  [Ent4]  | Cite_10 [Att11]  [Ent4]  | Abbr_10 [Att11]  [Ent4]  | Acronym_10 [Att11]  [Ent4]  | Q_10 [Att13]  [Ent4]  | Sub_10 [Att11]  [Ent4]  | Sup_10 [Att11]  [Ent4]  | Tt_10 [Att11]  [Ent4]  | I_10 [Att11]  [Ent4]  | B_10 [Att11]  [Ent4]  | Big_10 [Att11]  [Ent4]  | Small_10 [Att11]  [Ent4]  | Map_10 [Att24]  [Ent28]  | Label_10 [Att29]  [Ent29]  | Input_10 [Att30]  | Select_10 [Att31]  [Ent57]  | Textarea_10 [Att35]  [Ent5]  | Button_10 [Att39]  [Ent59]  | PCDATA_10 [Att0] B.ByteString
    deriving (Show)

data Ent11 = Script_11 [Att10]  [Ent101]  | Noscript_11 [Att11]  [Ent11]  | Div_11 [Att11]  [Ent12]  | P_11 [Att11]  [Ent13]  | H1_11 [Att11]  [Ent13]  | H2_11 [Att11]  [Ent13]  | H3_11 [Att11]  [Ent13]  | H4_11 [Att11]  [Ent13]  | H5_11 [Att11]  [Ent13]  | H6_11 [Att11]  [Ent13]  | Ul_11 [Att11]  [Ent14]  | Ol_11 [Att11]  [Ent14]  | Dl_11 [Att11]  [Ent15]  | Address_11 [Att11]  [Ent13]  | Hr_11 [Att11]  | Pre_11 [Att11]  [Ent16]  | Blockquote_11 [Att13]  [Ent11]  | Ins_11 [Att14]  [Ent12]  | Del_11 [Att14]  [Ent12]  | Fieldset_11 [Att11]  [Ent17]  | Table_11 [Att40]  [Ent18] 
    deriving (Show)

data Ent12 = Script_12 [Att10]  [Ent101]  | Noscript_12 [Att11]  [Ent11]  | Div_12 [Att11]  [Ent12]  | P_12 [Att11]  [Ent13]  | H1_12 [Att11]  [Ent13]  | H2_12 [Att11]  [Ent13]  | H3_12 [Att11]  [Ent13]  | H4_12 [Att11]  [Ent13]  | H5_12 [Att11]  [Ent13]  | H6_12 [Att11]  [Ent13]  | Ul_12 [Att11]  [Ent14]  | Ol_12 [Att11]  [Ent14]  | Dl_12 [Att11]  [Ent15]  | Address_12 [Att11]  [Ent13]  | Hr_12 [Att11]  | Pre_12 [Att11]  [Ent16]  | Blockquote_12 [Att13]  [Ent11]  | Ins_12 [Att14]  [Ent12]  | Del_12 [Att14]  [Ent12]  | Span_12 [Att11]  [Ent13]  | Bdo_12 [Att11]  [Ent13]  | Br_12 [Att18]  | Em_12 [Att11]  [Ent13]  | Strong_12 [Att11]  [Ent13]  | Dfn_12 [Att11]  [Ent13]  | Code_12 [Att11]  [Ent13]  | Samp_12 [Att11]  [Ent13]  | Kbd_12 [Att11]  [Ent13]  | Var_12 [Att11]  [Ent13]  | Cite_12 [Att11]  [Ent13]  | Abbr_12 [Att11]  [Ent13]  | Acronym_12 [Att11]  [Ent13]  | Q_12 [Att13]  [Ent13]  | Sub_12 [Att11]  [Ent13]  | Sup_12 [Att11]  [Ent13]  | Tt_12 [Att11]  [Ent13]  | I_12 [Att11]  [Ent13]  | B_12 [Att11]  [Ent13]  | Big_12 [Att11]  [Ent13]  | Small_12 [Att11]  [Ent13]  | Object_12 [Att19]  [Ent102]  | Img_12 [Att21]  | Map_12 [Att24]  [Ent103]  | Label_12 [Att29]  [Ent38]  | Input_12 [Att30]  | Select_12 [Att31]  [Ent110]  | Textarea_12 [Att35]  [Ent101]  | Fieldset_12 [Att11]  [Ent17]  | Button_12 [Att39]  [Ent112]  | Table_12 [Att40]  [Ent18]  | PCDATA_12 [Att0] B.ByteString
    deriving (Show)

data Ent13 = Script_13 [Att10]  [Ent101]  | Ins_13 [Att14]  [Ent12]  | Del_13 [Att14]  [Ent12]  | Span_13 [Att11]  [Ent13]  | Bdo_13 [Att11]  [Ent13]  | Br_13 [Att18]  | Em_13 [Att11]  [Ent13]  | Strong_13 [Att11]  [Ent13]  | Dfn_13 [Att11]  [Ent13]  | Code_13 [Att11]  [Ent13]  | Samp_13 [Att11]  [Ent13]  | Kbd_13 [Att11]  [Ent13]  | Var_13 [Att11]  [Ent13]  | Cite_13 [Att11]  [Ent13]  | Abbr_13 [Att11]  [Ent13]  | Acronym_13 [Att11]  [Ent13]  | Q_13 [Att13]  [Ent13]  | Sub_13 [Att11]  [Ent13]  | Sup_13 [Att11]  [Ent13]  | Tt_13 [Att11]  [Ent13]  | I_13 [Att11]  [Ent13]  | B_13 [Att11]  [Ent13]  | Big_13 [Att11]  [Ent13]  | Small_13 [Att11]  [Ent13]  | Object_13 [Att19]  [Ent102]  | Img_13 [Att21]  | Map_13 [Att24]  [Ent103]  | Label_13 [Att29]  [Ent38]  | Input_13 [Att30]  | Select_13 [Att31]  [Ent110]  | Textarea_13 [Att35]  [Ent101]  | Button_13 [Att39]  [Ent112]  | PCDATA_13 [Att0] B.ByteString
    deriving (Show)

data Ent14 = Li_14 [Att11]  [Ent12] 
    deriving (Show)

data Ent15 = Dt_15 [Att11]  [Ent13]  | Dd_15 [Att11]  [Ent12] 
    deriving (Show)

data Ent16 = Script_16 [Att10]  [Ent101]  | Ins_16 [Att14]  [Ent12]  | Del_16 [Att14]  [Ent12]  | Span_16 [Att11]  [Ent13]  | Bdo_16 [Att11]  [Ent13]  | Br_16 [Att18]  | Em_16 [Att11]  [Ent13]  | Strong_16 [Att11]  [Ent13]  | Dfn_16 [Att11]  [Ent13]  | Code_16 [Att11]  [Ent13]  | Samp_16 [Att11]  [Ent13]  | Kbd_16 [Att11]  [Ent13]  | Var_16 [Att11]  [Ent13]  | Cite_16 [Att11]  [Ent13]  | Abbr_16 [Att11]  [Ent13]  | Acronym_16 [Att11]  [Ent13]  | Q_16 [Att13]  [Ent13]  | Sub_16 [Att11]  [Ent13]  | Sup_16 [Att11]  [Ent13]  | Tt_16 [Att11]  [Ent13]  | I_16 [Att11]  [Ent13]  | B_16 [Att11]  [Ent13]  | Big_16 [Att11]  [Ent13]  | Small_16 [Att11]  [Ent13]  | Map_16 [Att24]  [Ent103]  | Label_16 [Att29]  [Ent38]  | Input_16 [Att30]  | Select_16 [Att31]  [Ent110]  | Textarea_16 [Att35]  [Ent101]  | Button_16 [Att39]  [Ent112]  | PCDATA_16 [Att0] B.ByteString
    deriving (Show)

data Ent17 = Script_17 [Att10]  [Ent101]  | Noscript_17 [Att11]  [Ent11]  | Div_17 [Att11]  [Ent12]  | P_17 [Att11]  [Ent13]  | H1_17 [Att11]  [Ent13]  | H2_17 [Att11]  [Ent13]  | H3_17 [Att11]  [Ent13]  | H4_17 [Att11]  [Ent13]  | H5_17 [Att11]  [Ent13]  | H6_17 [Att11]  [Ent13]  | Ul_17 [Att11]  [Ent14]  | Ol_17 [Att11]  [Ent14]  | Dl_17 [Att11]  [Ent15]  | Address_17 [Att11]  [Ent13]  | Hr_17 [Att11]  | Pre_17 [Att11]  [Ent16]  | Blockquote_17 [Att13]  [Ent11]  | Ins_17 [Att14]  [Ent12]  | Del_17 [Att14]  [Ent12]  | Span_17 [Att11]  [Ent13]  | Bdo_17 [Att11]  [Ent13]  | Br_17 [Att18]  | Em_17 [Att11]  [Ent13]  | Strong_17 [Att11]  [Ent13]  | Dfn_17 [Att11]  [Ent13]  | Code_17 [Att11]  [Ent13]  | Samp_17 [Att11]  [Ent13]  | Kbd_17 [Att11]  [Ent13]  | Var_17 [Att11]  [Ent13]  | Cite_17 [Att11]  [Ent13]  | Abbr_17 [Att11]  [Ent13]  | Acronym_17 [Att11]  [Ent13]  | Q_17 [Att13]  [Ent13]  | Sub_17 [Att11]  [Ent13]  | Sup_17 [Att11]  [Ent13]  | Tt_17 [Att11]  [Ent13]  | I_17 [Att11]  [Ent13]  | B_17 [Att11]  [Ent13]  | Big_17 [Att11]  [Ent13]  | Small_17 [Att11]  [Ent13]  | Object_17 [Att19]  [Ent102]  | Img_17 [Att21]  | Map_17 [Att24]  [Ent103]  | Label_17 [Att29]  [Ent38]  | Input_17 [Att30]  | Select_17 [Att31]  [Ent110]  | Textarea_17 [Att35]  [Ent101]  | Fieldset_17 [Att11]  [Ent17]  | Legend_17 [Att38]  [Ent13]  | Button_17 [Att39]  [Ent112]  | Table_17 [Att40]  [Ent18]  | PCDATA_17 [Att0] B.ByteString
    deriving (Show)

data Ent18 = Caption_18 [Att11]  [Ent13]  | Thead_18 [Att41]  [Ent19]  | Tfoot_18 [Att41]  [Ent19]  | Tbody_18 [Att41]  [Ent19]  | Colgroup_18 [Att42]  [Ent20]  | Col_18 [Att42]  | Tr_18 [Att41]  [Ent21] 
    deriving (Show)

data Ent19 = Tr_19 [Att41]  [Ent21] 
    deriving (Show)

data Ent20 = Col_20 [Att42] 
    deriving (Show)

data Ent21 = Th_21 [Att43]  [Ent12]  | Td_21 [Att43]  [Ent12] 
    deriving (Show)

data Ent22 = Script_22 [Att10]  [Ent5]  | Noscript_22 [Att11]  [Ent7]  | Div_22 [Att11]  [Ent6]  | P_22 [Att11]  [Ent4]  | H1_22 [Att11]  [Ent4]  | H2_22 [Att11]  [Ent4]  | H3_22 [Att11]  [Ent4]  | H4_22 [Att11]  [Ent4]  | H5_22 [Att11]  [Ent4]  | H6_22 [Att11]  [Ent4]  | Ul_22 [Att11]  [Ent8]  | Ol_22 [Att11]  [Ent8]  | Dl_22 [Att11]  [Ent9]  | Address_22 [Att11]  [Ent4]  | Hr_22 [Att11]  | Pre_22 [Att11]  [Ent10]  | Blockquote_22 [Att13]  [Ent7]  | Ins_22 [Att14]  [Ent6]  | Del_22 [Att14]  [Ent6]  | Span_22 [Att11]  [Ent4]  | Bdo_22 [Att11]  [Ent4]  | Br_22 [Att18]  | Em_22 [Att11]  [Ent4]  | Strong_22 [Att11]  [Ent4]  | Dfn_22 [Att11]  [Ent4]  | Code_22 [Att11]  [Ent4]  | Samp_22 [Att11]  [Ent4]  | Kbd_22 [Att11]  [Ent4]  | Var_22 [Att11]  [Ent4]  | Cite_22 [Att11]  [Ent4]  | Abbr_22 [Att11]  [Ent4]  | Acronym_22 [Att11]  [Ent4]  | Q_22 [Att13]  [Ent4]  | Sub_22 [Att11]  [Ent4]  | Sup_22 [Att11]  [Ent4]  | Tt_22 [Att11]  [Ent4]  | I_22 [Att11]  [Ent4]  | B_22 [Att11]  [Ent4]  | Big_22 [Att11]  [Ent4]  | Small_22 [Att11]  [Ent4]  | Object_22 [Att19]  [Ent27]  | Img_22 [Att21]  | Map_22 [Att24]  [Ent28]  | Form_22 [Att27]  [Ent11]  | Label_22 [Att29]  [Ent29]  | Input_22 [Att30]  | Select_22 [Att31]  [Ent57]  | Textarea_22 [Att35]  [Ent5]  | Fieldset_22 [Att11]  [Ent22]  | Legend_22 [Att38]  [Ent4]  | Button_22 [Att39]  [Ent59]  | Table_22 [Att40]  [Ent23]  | PCDATA_22 [Att0] B.ByteString
    deriving (Show)

data Ent23 = Caption_23 [Att11]  [Ent4]  | Thead_23 [Att41]  [Ent24]  | Tfoot_23 [Att41]  [Ent24]  | Tbody_23 [Att41]  [Ent24]  | Colgroup_23 [Att42]  [Ent25]  | Col_23 [Att42]  | Tr_23 [Att41]  [Ent26] 
    deriving (Show)

data Ent24 = Tr_24 [Att41]  [Ent26] 
    deriving (Show)

data Ent25 = Col_25 [Att42] 
    deriving (Show)

data Ent26 = Th_26 [Att43]  [Ent6]  | Td_26 [Att43]  [Ent6] 
    deriving (Show)

data Ent27 = Script_27 [Att10]  [Ent5]  | Noscript_27 [Att11]  [Ent7]  | Div_27 [Att11]  [Ent6]  | P_27 [Att11]  [Ent4]  | H1_27 [Att11]  [Ent4]  | H2_27 [Att11]  [Ent4]  | H3_27 [Att11]  [Ent4]  | H4_27 [Att11]  [Ent4]  | H5_27 [Att11]  [Ent4]  | H6_27 [Att11]  [Ent4]  | Ul_27 [Att11]  [Ent8]  | Ol_27 [Att11]  [Ent8]  | Dl_27 [Att11]  [Ent9]  | Address_27 [Att11]  [Ent4]  | Hr_27 [Att11]  | Pre_27 [Att11]  [Ent10]  | Blockquote_27 [Att13]  [Ent7]  | Ins_27 [Att14]  [Ent6]  | Del_27 [Att14]  [Ent6]  | Span_27 [Att11]  [Ent4]  | Bdo_27 [Att11]  [Ent4]  | Br_27 [Att18]  | Em_27 [Att11]  [Ent4]  | Strong_27 [Att11]  [Ent4]  | Dfn_27 [Att11]  [Ent4]  | Code_27 [Att11]  [Ent4]  | Samp_27 [Att11]  [Ent4]  | Kbd_27 [Att11]  [Ent4]  | Var_27 [Att11]  [Ent4]  | Cite_27 [Att11]  [Ent4]  | Abbr_27 [Att11]  [Ent4]  | Acronym_27 [Att11]  [Ent4]  | Q_27 [Att13]  [Ent4]  | Sub_27 [Att11]  [Ent4]  | Sup_27 [Att11]  [Ent4]  | Tt_27 [Att11]  [Ent4]  | I_27 [Att11]  [Ent4]  | B_27 [Att11]  [Ent4]  | Big_27 [Att11]  [Ent4]  | Small_27 [Att11]  [Ent4]  | Object_27 [Att19]  [Ent27]  | Param_27 [Att20]  | Img_27 [Att21]  | Map_27 [Att24]  [Ent28]  | Form_27 [Att27]  [Ent11]  | Label_27 [Att29]  [Ent29]  | Input_27 [Att30]  | Select_27 [Att31]  [Ent57]  | Textarea_27 [Att35]  [Ent5]  | Fieldset_27 [Att11]  [Ent22]  | Button_27 [Att39]  [Ent59]  | Table_27 [Att40]  [Ent23]  | PCDATA_27 [Att0] B.ByteString
    deriving (Show)

data Ent28 = Script_28 [Att10]  [Ent5]  | Noscript_28 [Att11]  [Ent7]  | Div_28 [Att11]  [Ent6]  | P_28 [Att11]  [Ent4]  | H1_28 [Att11]  [Ent4]  | H2_28 [Att11]  [Ent4]  | H3_28 [Att11]  [Ent4]  | H4_28 [Att11]  [Ent4]  | H5_28 [Att11]  [Ent4]  | H6_28 [Att11]  [Ent4]  | Ul_28 [Att11]  [Ent8]  | Ol_28 [Att11]  [Ent8]  | Dl_28 [Att11]  [Ent9]  | Address_28 [Att11]  [Ent4]  | Hr_28 [Att11]  | Pre_28 [Att11]  [Ent10]  | Blockquote_28 [Att13]  [Ent7]  | Ins_28 [Att14]  [Ent6]  | Del_28 [Att14]  [Ent6]  | Area_28 [Att26]  | Form_28 [Att27]  [Ent11]  | Fieldset_28 [Att11]  [Ent22]  | Table_28 [Att40]  [Ent23] 
    deriving (Show)

data Ent29 = Script_29 [Att10]  [Ent30]  | Ins_29 [Att14]  [Ent31]  | Del_29 [Att14]  [Ent31]  | Span_29 [Att11]  [Ent29]  | Bdo_29 [Att11]  [Ent29]  | Br_29 [Att18]  | Em_29 [Att11]  [Ent29]  | Strong_29 [Att11]  [Ent29]  | Dfn_29 [Att11]  [Ent29]  | Code_29 [Att11]  [Ent29]  | Samp_29 [Att11]  [Ent29]  | Kbd_29 [Att11]  [Ent29]  | Var_29 [Att11]  [Ent29]  | Cite_29 [Att11]  [Ent29]  | Abbr_29 [Att11]  [Ent29]  | Acronym_29 [Att11]  [Ent29]  | Q_29 [Att13]  [Ent29]  | Sub_29 [Att11]  [Ent29]  | Sup_29 [Att11]  [Ent29]  | Tt_29 [Att11]  [Ent29]  | I_29 [Att11]  [Ent29]  | B_29 [Att11]  [Ent29]  | Big_29 [Att11]  [Ent29]  | Small_29 [Att11]  [Ent29]  | Object_29 [Att19]  [Ent52]  | Img_29 [Att21]  | Map_29 [Att24]  [Ent53]  | Input_29 [Att30]  | Select_29 [Att31]  [Ent54]  | Textarea_29 [Att35]  [Ent30]  | Button_29 [Att39]  [Ent56]  | PCDATA_29 [Att0] B.ByteString
    deriving (Show)

data Ent30 = PCDATA_30 [Att0] B.ByteString
    deriving (Show)

data Ent31 = Script_31 [Att10]  [Ent30]  | Noscript_31 [Att11]  [Ent32]  | Div_31 [Att11]  [Ent31]  | P_31 [Att11]  [Ent29]  | H1_31 [Att11]  [Ent29]  | H2_31 [Att11]  [Ent29]  | H3_31 [Att11]  [Ent29]  | H4_31 [Att11]  [Ent29]  | H5_31 [Att11]  [Ent29]  | H6_31 [Att11]  [Ent29]  | Ul_31 [Att11]  [Ent33]  | Ol_31 [Att11]  [Ent33]  | Dl_31 [Att11]  [Ent34]  | Address_31 [Att11]  [Ent29]  | Hr_31 [Att11]  | Pre_31 [Att11]  [Ent35]  | Blockquote_31 [Att13]  [Ent32]  | Ins_31 [Att14]  [Ent31]  | Del_31 [Att14]  [Ent31]  | Span_31 [Att11]  [Ent29]  | Bdo_31 [Att11]  [Ent29]  | Br_31 [Att18]  | Em_31 [Att11]  [Ent29]  | Strong_31 [Att11]  [Ent29]  | Dfn_31 [Att11]  [Ent29]  | Code_31 [Att11]  [Ent29]  | Samp_31 [Att11]  [Ent29]  | Kbd_31 [Att11]  [Ent29]  | Var_31 [Att11]  [Ent29]  | Cite_31 [Att11]  [Ent29]  | Abbr_31 [Att11]  [Ent29]  | Acronym_31 [Att11]  [Ent29]  | Q_31 [Att13]  [Ent29]  | Sub_31 [Att11]  [Ent29]  | Sup_31 [Att11]  [Ent29]  | Tt_31 [Att11]  [Ent29]  | I_31 [Att11]  [Ent29]  | B_31 [Att11]  [Ent29]  | Big_31 [Att11]  [Ent29]  | Small_31 [Att11]  [Ent29]  | Object_31 [Att19]  [Ent52]  | Img_31 [Att21]  | Map_31 [Att24]  [Ent53]  | Form_31 [Att27]  [Ent36]  | Input_31 [Att30]  | Select_31 [Att31]  [Ent54]  | Textarea_31 [Att35]  [Ent30]  | Fieldset_31 [Att11]  [Ent47]  | Button_31 [Att39]  [Ent56]  | Table_31 [Att40]  [Ent48]  | PCDATA_31 [Att0] B.ByteString
    deriving (Show)

data Ent32 = Script_32 [Att10]  [Ent30]  | Noscript_32 [Att11]  [Ent32]  | Div_32 [Att11]  [Ent31]  | P_32 [Att11]  [Ent29]  | H1_32 [Att11]  [Ent29]  | H2_32 [Att11]  [Ent29]  | H3_32 [Att11]  [Ent29]  | H4_32 [Att11]  [Ent29]  | H5_32 [Att11]  [Ent29]  | H6_32 [Att11]  [Ent29]  | Ul_32 [Att11]  [Ent33]  | Ol_32 [Att11]  [Ent33]  | Dl_32 [Att11]  [Ent34]  | Address_32 [Att11]  [Ent29]  | Hr_32 [Att11]  | Pre_32 [Att11]  [Ent35]  | Blockquote_32 [Att13]  [Ent32]  | Ins_32 [Att14]  [Ent31]  | Del_32 [Att14]  [Ent31]  | Form_32 [Att27]  [Ent36]  | Fieldset_32 [Att11]  [Ent47]  | Table_32 [Att40]  [Ent48] 
    deriving (Show)

data Ent33 = Li_33 [Att11]  [Ent31] 
    deriving (Show)

data Ent34 = Dt_34 [Att11]  [Ent29]  | Dd_34 [Att11]  [Ent31] 
    deriving (Show)

data Ent35 = Script_35 [Att10]  [Ent30]  | Ins_35 [Att14]  [Ent31]  | Del_35 [Att14]  [Ent31]  | Span_35 [Att11]  [Ent29]  | Bdo_35 [Att11]  [Ent29]  | Br_35 [Att18]  | Em_35 [Att11]  [Ent29]  | Strong_35 [Att11]  [Ent29]  | Dfn_35 [Att11]  [Ent29]  | Code_35 [Att11]  [Ent29]  | Samp_35 [Att11]  [Ent29]  | Kbd_35 [Att11]  [Ent29]  | Var_35 [Att11]  [Ent29]  | Cite_35 [Att11]  [Ent29]  | Abbr_35 [Att11]  [Ent29]  | Acronym_35 [Att11]  [Ent29]  | Q_35 [Att13]  [Ent29]  | Sub_35 [Att11]  [Ent29]  | Sup_35 [Att11]  [Ent29]  | Tt_35 [Att11]  [Ent29]  | I_35 [Att11]  [Ent29]  | B_35 [Att11]  [Ent29]  | Big_35 [Att11]  [Ent29]  | Small_35 [Att11]  [Ent29]  | Map_35 [Att24]  [Ent53]  | Input_35 [Att30]  | Select_35 [Att31]  [Ent54]  | Textarea_35 [Att35]  [Ent30]  | Button_35 [Att39]  [Ent56]  | PCDATA_35 [Att0] B.ByteString
    deriving (Show)

data Ent36 = Script_36 [Att10]  [Ent104]  | Noscript_36 [Att11]  [Ent36]  | Div_36 [Att11]  [Ent37]  | P_36 [Att11]  [Ent38]  | H1_36 [Att11]  [Ent38]  | H2_36 [Att11]  [Ent38]  | H3_36 [Att11]  [Ent38]  | H4_36 [Att11]  [Ent38]  | H5_36 [Att11]  [Ent38]  | H6_36 [Att11]  [Ent38]  | Ul_36 [Att11]  [Ent39]  | Ol_36 [Att11]  [Ent39]  | Dl_36 [Att11]  [Ent40]  | Address_36 [Att11]  [Ent38]  | Hr_36 [Att11]  | Pre_36 [Att11]  [Ent41]  | Blockquote_36 [Att13]  [Ent36]  | Ins_36 [Att14]  [Ent37]  | Del_36 [Att14]  [Ent37]  | Fieldset_36 [Att11]  [Ent42]  | Table_36 [Att40]  [Ent43] 
    deriving (Show)

data Ent37 = Script_37 [Att10]  [Ent104]  | Noscript_37 [Att11]  [Ent36]  | Div_37 [Att11]  [Ent37]  | P_37 [Att11]  [Ent38]  | H1_37 [Att11]  [Ent38]  | H2_37 [Att11]  [Ent38]  | H3_37 [Att11]  [Ent38]  | H4_37 [Att11]  [Ent38]  | H5_37 [Att11]  [Ent38]  | H6_37 [Att11]  [Ent38]  | Ul_37 [Att11]  [Ent39]  | Ol_37 [Att11]  [Ent39]  | Dl_37 [Att11]  [Ent40]  | Address_37 [Att11]  [Ent38]  | Hr_37 [Att11]  | Pre_37 [Att11]  [Ent41]  | Blockquote_37 [Att13]  [Ent36]  | Ins_37 [Att14]  [Ent37]  | Del_37 [Att14]  [Ent37]  | Span_37 [Att11]  [Ent38]  | Bdo_37 [Att11]  [Ent38]  | Br_37 [Att18]  | Em_37 [Att11]  [Ent38]  | Strong_37 [Att11]  [Ent38]  | Dfn_37 [Att11]  [Ent38]  | Code_37 [Att11]  [Ent38]  | Samp_37 [Att11]  [Ent38]  | Kbd_37 [Att11]  [Ent38]  | Var_37 [Att11]  [Ent38]  | Cite_37 [Att11]  [Ent38]  | Abbr_37 [Att11]  [Ent38]  | Acronym_37 [Att11]  [Ent38]  | Q_37 [Att13]  [Ent38]  | Sub_37 [Att11]  [Ent38]  | Sup_37 [Att11]  [Ent38]  | Tt_37 [Att11]  [Ent38]  | I_37 [Att11]  [Ent38]  | B_37 [Att11]  [Ent38]  | Big_37 [Att11]  [Ent38]  | Small_37 [Att11]  [Ent38]  | Object_37 [Att19]  [Ent105]  | Img_37 [Att21]  | Map_37 [Att24]  [Ent106]  | Input_37 [Att30]  | Select_37 [Att31]  [Ent107]  | Textarea_37 [Att35]  [Ent104]  | Fieldset_37 [Att11]  [Ent42]  | Button_37 [Att39]  [Ent109]  | Table_37 [Att40]  [Ent43]  | PCDATA_37 [Att0] B.ByteString
    deriving (Show)

data Ent38 = Script_38 [Att10]  [Ent104]  | Ins_38 [Att14]  [Ent37]  | Del_38 [Att14]  [Ent37]  | Span_38 [Att11]  [Ent38]  | Bdo_38 [Att11]  [Ent38]  | Br_38 [Att18]  | Em_38 [Att11]  [Ent38]  | Strong_38 [Att11]  [Ent38]  | Dfn_38 [Att11]  [Ent38]  | Code_38 [Att11]  [Ent38]  | Samp_38 [Att11]  [Ent38]  | Kbd_38 [Att11]  [Ent38]  | Var_38 [Att11]  [Ent38]  | Cite_38 [Att11]  [Ent38]  | Abbr_38 [Att11]  [Ent38]  | Acronym_38 [Att11]  [Ent38]  | Q_38 [Att13]  [Ent38]  | Sub_38 [Att11]  [Ent38]  | Sup_38 [Att11]  [Ent38]  | Tt_38 [Att11]  [Ent38]  | I_38 [Att11]  [Ent38]  | B_38 [Att11]  [Ent38]  | Big_38 [Att11]  [Ent38]  | Small_38 [Att11]  [Ent38]  | Object_38 [Att19]  [Ent105]  | Img_38 [Att21]  | Map_38 [Att24]  [Ent106]  | Input_38 [Att30]  | Select_38 [Att31]  [Ent107]  | Textarea_38 [Att35]  [Ent104]  | Button_38 [Att39]  [Ent109]  | PCDATA_38 [Att0] B.ByteString
    deriving (Show)

data Ent39 = Li_39 [Att11]  [Ent37] 
    deriving (Show)

data Ent40 = Dt_40 [Att11]  [Ent38]  | Dd_40 [Att11]  [Ent37] 
    deriving (Show)

data Ent41 = Script_41 [Att10]  [Ent104]  | Ins_41 [Att14]  [Ent37]  | Del_41 [Att14]  [Ent37]  | Span_41 [Att11]  [Ent38]  | Bdo_41 [Att11]  [Ent38]  | Br_41 [Att18]  | Em_41 [Att11]  [Ent38]  | Strong_41 [Att11]  [Ent38]  | Dfn_41 [Att11]  [Ent38]  | Code_41 [Att11]  [Ent38]  | Samp_41 [Att11]  [Ent38]  | Kbd_41 [Att11]  [Ent38]  | Var_41 [Att11]  [Ent38]  | Cite_41 [Att11]  [Ent38]  | Abbr_41 [Att11]  [Ent38]  | Acronym_41 [Att11]  [Ent38]  | Q_41 [Att13]  [Ent38]  | Sub_41 [Att11]  [Ent38]  | Sup_41 [Att11]  [Ent38]  | Tt_41 [Att11]  [Ent38]  | I_41 [Att11]  [Ent38]  | B_41 [Att11]  [Ent38]  | Big_41 [Att11]  [Ent38]  | Small_41 [Att11]  [Ent38]  | Map_41 [Att24]  [Ent106]  | Input_41 [Att30]  | Select_41 [Att31]  [Ent107]  | Textarea_41 [Att35]  [Ent104]  | Button_41 [Att39]  [Ent109]  | PCDATA_41 [Att0] B.ByteString
    deriving (Show)

data Ent42 = Script_42 [Att10]  [Ent104]  | Noscript_42 [Att11]  [Ent36]  | Div_42 [Att11]  [Ent37]  | P_42 [Att11]  [Ent38]  | H1_42 [Att11]  [Ent38]  | H2_42 [Att11]  [Ent38]  | H3_42 [Att11]  [Ent38]  | H4_42 [Att11]  [Ent38]  | H5_42 [Att11]  [Ent38]  | H6_42 [Att11]  [Ent38]  | Ul_42 [Att11]  [Ent39]  | Ol_42 [Att11]  [Ent39]  | Dl_42 [Att11]  [Ent40]  | Address_42 [Att11]  [Ent38]  | Hr_42 [Att11]  | Pre_42 [Att11]  [Ent41]  | Blockquote_42 [Att13]  [Ent36]  | Ins_42 [Att14]  [Ent37]  | Del_42 [Att14]  [Ent37]  | Span_42 [Att11]  [Ent38]  | Bdo_42 [Att11]  [Ent38]  | Br_42 [Att18]  | Em_42 [Att11]  [Ent38]  | Strong_42 [Att11]  [Ent38]  | Dfn_42 [Att11]  [Ent38]  | Code_42 [Att11]  [Ent38]  | Samp_42 [Att11]  [Ent38]  | Kbd_42 [Att11]  [Ent38]  | Var_42 [Att11]  [Ent38]  | Cite_42 [Att11]  [Ent38]  | Abbr_42 [Att11]  [Ent38]  | Acronym_42 [Att11]  [Ent38]  | Q_42 [Att13]  [Ent38]  | Sub_42 [Att11]  [Ent38]  | Sup_42 [Att11]  [Ent38]  | Tt_42 [Att11]  [Ent38]  | I_42 [Att11]  [Ent38]  | B_42 [Att11]  [Ent38]  | Big_42 [Att11]  [Ent38]  | Small_42 [Att11]  [Ent38]  | Object_42 [Att19]  [Ent105]  | Img_42 [Att21]  | Map_42 [Att24]  [Ent106]  | Input_42 [Att30]  | Select_42 [Att31]  [Ent107]  | Textarea_42 [Att35]  [Ent104]  | Fieldset_42 [Att11]  [Ent42]  | Legend_42 [Att38]  [Ent38]  | Button_42 [Att39]  [Ent109]  | Table_42 [Att40]  [Ent43]  | PCDATA_42 [Att0] B.ByteString
    deriving (Show)

data Ent43 = Caption_43 [Att11]  [Ent38]  | Thead_43 [Att41]  [Ent44]  | Tfoot_43 [Att41]  [Ent44]  | Tbody_43 [Att41]  [Ent44]  | Colgroup_43 [Att42]  [Ent45]  | Col_43 [Att42]  | Tr_43 [Att41]  [Ent46] 
    deriving (Show)

data Ent44 = Tr_44 [Att41]  [Ent46] 
    deriving (Show)

data Ent45 = Col_45 [Att42] 
    deriving (Show)

data Ent46 = Th_46 [Att43]  [Ent37]  | Td_46 [Att43]  [Ent37] 
    deriving (Show)

data Ent47 = Script_47 [Att10]  [Ent30]  | Noscript_47 [Att11]  [Ent32]  | Div_47 [Att11]  [Ent31]  | P_47 [Att11]  [Ent29]  | H1_47 [Att11]  [Ent29]  | H2_47 [Att11]  [Ent29]  | H3_47 [Att11]  [Ent29]  | H4_47 [Att11]  [Ent29]  | H5_47 [Att11]  [Ent29]  | H6_47 [Att11]  [Ent29]  | Ul_47 [Att11]  [Ent33]  | Ol_47 [Att11]  [Ent33]  | Dl_47 [Att11]  [Ent34]  | Address_47 [Att11]  [Ent29]  | Hr_47 [Att11]  | Pre_47 [Att11]  [Ent35]  | Blockquote_47 [Att13]  [Ent32]  | Ins_47 [Att14]  [Ent31]  | Del_47 [Att14]  [Ent31]  | Span_47 [Att11]  [Ent29]  | Bdo_47 [Att11]  [Ent29]  | Br_47 [Att18]  | Em_47 [Att11]  [Ent29]  | Strong_47 [Att11]  [Ent29]  | Dfn_47 [Att11]  [Ent29]  | Code_47 [Att11]  [Ent29]  | Samp_47 [Att11]  [Ent29]  | Kbd_47 [Att11]  [Ent29]  | Var_47 [Att11]  [Ent29]  | Cite_47 [Att11]  [Ent29]  | Abbr_47 [Att11]  [Ent29]  | Acronym_47 [Att11]  [Ent29]  | Q_47 [Att13]  [Ent29]  | Sub_47 [Att11]  [Ent29]  | Sup_47 [Att11]  [Ent29]  | Tt_47 [Att11]  [Ent29]  | I_47 [Att11]  [Ent29]  | B_47 [Att11]  [Ent29]  | Big_47 [Att11]  [Ent29]  | Small_47 [Att11]  [Ent29]  | Object_47 [Att19]  [Ent52]  | Img_47 [Att21]  | Map_47 [Att24]  [Ent53]  | Form_47 [Att27]  [Ent36]  | Input_47 [Att30]  | Select_47 [Att31]  [Ent54]  | Textarea_47 [Att35]  [Ent30]  | Fieldset_47 [Att11]  [Ent47]  | Legend_47 [Att38]  [Ent29]  | Button_47 [Att39]  [Ent56]  | Table_47 [Att40]  [Ent48]  | PCDATA_47 [Att0] B.ByteString
    deriving (Show)

data Ent48 = Caption_48 [Att11]  [Ent29]  | Thead_48 [Att41]  [Ent49]  | Tfoot_48 [Att41]  [Ent49]  | Tbody_48 [Att41]  [Ent49]  | Colgroup_48 [Att42]  [Ent50]  | Col_48 [Att42]  | Tr_48 [Att41]  [Ent51] 
    deriving (Show)

data Ent49 = Tr_49 [Att41]  [Ent51] 
    deriving (Show)

data Ent50 = Col_50 [Att42] 
    deriving (Show)

data Ent51 = Th_51 [Att43]  [Ent31]  | Td_51 [Att43]  [Ent31] 
    deriving (Show)

data Ent52 = Script_52 [Att10]  [Ent30]  | Noscript_52 [Att11]  [Ent32]  | Div_52 [Att11]  [Ent31]  | P_52 [Att11]  [Ent29]  | H1_52 [Att11]  [Ent29]  | H2_52 [Att11]  [Ent29]  | H3_52 [Att11]  [Ent29]  | H4_52 [Att11]  [Ent29]  | H5_52 [Att11]  [Ent29]  | H6_52 [Att11]  [Ent29]  | Ul_52 [Att11]  [Ent33]  | Ol_52 [Att11]  [Ent33]  | Dl_52 [Att11]  [Ent34]  | Address_52 [Att11]  [Ent29]  | Hr_52 [Att11]  | Pre_52 [Att11]  [Ent35]  | Blockquote_52 [Att13]  [Ent32]  | Ins_52 [Att14]  [Ent31]  | Del_52 [Att14]  [Ent31]  | Span_52 [Att11]  [Ent29]  | Bdo_52 [Att11]  [Ent29]  | Br_52 [Att18]  | Em_52 [Att11]  [Ent29]  | Strong_52 [Att11]  [Ent29]  | Dfn_52 [Att11]  [Ent29]  | Code_52 [Att11]  [Ent29]  | Samp_52 [Att11]  [Ent29]  | Kbd_52 [Att11]  [Ent29]  | Var_52 [Att11]  [Ent29]  | Cite_52 [Att11]  [Ent29]  | Abbr_52 [Att11]  [Ent29]  | Acronym_52 [Att11]  [Ent29]  | Q_52 [Att13]  [Ent29]  | Sub_52 [Att11]  [Ent29]  | Sup_52 [Att11]  [Ent29]  | Tt_52 [Att11]  [Ent29]  | I_52 [Att11]  [Ent29]  | B_52 [Att11]  [Ent29]  | Big_52 [Att11]  [Ent29]  | Small_52 [Att11]  [Ent29]  | Object_52 [Att19]  [Ent52]  | Param_52 [Att20]  | Img_52 [Att21]  | Map_52 [Att24]  [Ent53]  | Form_52 [Att27]  [Ent36]  | Input_52 [Att30]  | Select_52 [Att31]  [Ent54]  | Textarea_52 [Att35]  [Ent30]  | Fieldset_52 [Att11]  [Ent47]  | Button_52 [Att39]  [Ent56]  | Table_52 [Att40]  [Ent48]  | PCDATA_52 [Att0] B.ByteString
    deriving (Show)

data Ent53 = Script_53 [Att10]  [Ent30]  | Noscript_53 [Att11]  [Ent32]  | Div_53 [Att11]  [Ent31]  | P_53 [Att11]  [Ent29]  | H1_53 [Att11]  [Ent29]  | H2_53 [Att11]  [Ent29]  | H3_53 [Att11]  [Ent29]  | H4_53 [Att11]  [Ent29]  | H5_53 [Att11]  [Ent29]  | H6_53 [Att11]  [Ent29]  | Ul_53 [Att11]  [Ent33]  | Ol_53 [Att11]  [Ent33]  | Dl_53 [Att11]  [Ent34]  | Address_53 [Att11]  [Ent29]  | Hr_53 [Att11]  | Pre_53 [Att11]  [Ent35]  | Blockquote_53 [Att13]  [Ent32]  | Ins_53 [Att14]  [Ent31]  | Del_53 [Att14]  [Ent31]  | Area_53 [Att26]  | Form_53 [Att27]  [Ent36]  | Fieldset_53 [Att11]  [Ent47]  | Table_53 [Att40]  [Ent48] 
    deriving (Show)

data Ent54 = Optgroup_54 [Att32]  [Ent55]  | Option_54 [Att34]  [Ent30] 
    deriving (Show)

data Ent55 = Option_55 [Att34]  [Ent30] 
    deriving (Show)

data Ent56 = Script_56 [Att10]  [Ent30]  | Noscript_56 [Att11]  [Ent32]  | Div_56 [Att11]  [Ent31]  | P_56 [Att11]  [Ent29]  | H1_56 [Att11]  [Ent29]  | H2_56 [Att11]  [Ent29]  | H3_56 [Att11]  [Ent29]  | H4_56 [Att11]  [Ent29]  | H5_56 [Att11]  [Ent29]  | H6_56 [Att11]  [Ent29]  | Ul_56 [Att11]  [Ent33]  | Ol_56 [Att11]  [Ent33]  | Dl_56 [Att11]  [Ent34]  | Address_56 [Att11]  [Ent29]  | Hr_56 [Att11]  | Pre_56 [Att11]  [Ent35]  | Blockquote_56 [Att13]  [Ent32]  | Ins_56 [Att14]  [Ent31]  | Del_56 [Att14]  [Ent31]  | Span_56 [Att11]  [Ent29]  | Bdo_56 [Att11]  [Ent29]  | Br_56 [Att18]  | Em_56 [Att11]  [Ent29]  | Strong_56 [Att11]  [Ent29]  | Dfn_56 [Att11]  [Ent29]  | Code_56 [Att11]  [Ent29]  | Samp_56 [Att11]  [Ent29]  | Kbd_56 [Att11]  [Ent29]  | Var_56 [Att11]  [Ent29]  | Cite_56 [Att11]  [Ent29]  | Abbr_56 [Att11]  [Ent29]  | Acronym_56 [Att11]  [Ent29]  | Q_56 [Att13]  [Ent29]  | Sub_56 [Att11]  [Ent29]  | Sup_56 [Att11]  [Ent29]  | Tt_56 [Att11]  [Ent29]  | I_56 [Att11]  [Ent29]  | B_56 [Att11]  [Ent29]  | Big_56 [Att11]  [Ent29]  | Small_56 [Att11]  [Ent29]  | Object_56 [Att19]  [Ent52]  | Img_56 [Att21]  | Map_56 [Att24]  [Ent53]  | Table_56 [Att40]  [Ent48]  | PCDATA_56 [Att0] B.ByteString
    deriving (Show)

data Ent57 = Optgroup_57 [Att32]  [Ent58]  | Option_57 [Att34]  [Ent5] 
    deriving (Show)

data Ent58 = Option_58 [Att34]  [Ent5] 
    deriving (Show)

data Ent59 = Script_59 [Att10]  [Ent5]  | Noscript_59 [Att11]  [Ent7]  | Div_59 [Att11]  [Ent6]  | P_59 [Att11]  [Ent4]  | H1_59 [Att11]  [Ent4]  | H2_59 [Att11]  [Ent4]  | H3_59 [Att11]  [Ent4]  | H4_59 [Att11]  [Ent4]  | H5_59 [Att11]  [Ent4]  | H6_59 [Att11]  [Ent4]  | Ul_59 [Att11]  [Ent8]  | Ol_59 [Att11]  [Ent8]  | Dl_59 [Att11]  [Ent9]  | Address_59 [Att11]  [Ent4]  | Hr_59 [Att11]  | Pre_59 [Att11]  [Ent10]  | Blockquote_59 [Att13]  [Ent7]  | Ins_59 [Att14]  [Ent6]  | Del_59 [Att14]  [Ent6]  | Span_59 [Att11]  [Ent4]  | Bdo_59 [Att11]  [Ent4]  | Br_59 [Att18]  | Em_59 [Att11]  [Ent4]  | Strong_59 [Att11]  [Ent4]  | Dfn_59 [Att11]  [Ent4]  | Code_59 [Att11]  [Ent4]  | Samp_59 [Att11]  [Ent4]  | Kbd_59 [Att11]  [Ent4]  | Var_59 [Att11]  [Ent4]  | Cite_59 [Att11]  [Ent4]  | Abbr_59 [Att11]  [Ent4]  | Acronym_59 [Att11]  [Ent4]  | Q_59 [Att13]  [Ent4]  | Sub_59 [Att11]  [Ent4]  | Sup_59 [Att11]  [Ent4]  | Tt_59 [Att11]  [Ent4]  | I_59 [Att11]  [Ent4]  | B_59 [Att11]  [Ent4]  | Big_59 [Att11]  [Ent4]  | Small_59 [Att11]  [Ent4]  | Object_59 [Att19]  [Ent27]  | Img_59 [Att21]  | Map_59 [Att24]  [Ent28]  | Table_59 [Att40]  [Ent23]  | PCDATA_59 [Att0] B.ByteString
    deriving (Show)

data Ent60 = Script_60 [Att10]  [Ent2]  | Ins_60 [Att14]  [Ent94]  | Del_60 [Att14]  [Ent94]  | A_60 [Att15]  [Ent4]  | Span_60 [Att11]  [Ent60]  | Bdo_60 [Att11]  [Ent60]  | Br_60 [Att18]  | Em_60 [Att11]  [Ent60]  | Strong_60 [Att11]  [Ent60]  | Dfn_60 [Att11]  [Ent60]  | Code_60 [Att11]  [Ent60]  | Samp_60 [Att11]  [Ent60]  | Kbd_60 [Att11]  [Ent60]  | Var_60 [Att11]  [Ent60]  | Cite_60 [Att11]  [Ent60]  | Abbr_60 [Att11]  [Ent60]  | Acronym_60 [Att11]  [Ent60]  | Q_60 [Att13]  [Ent60]  | Sub_60 [Att11]  [Ent60]  | Sup_60 [Att11]  [Ent60]  | Tt_60 [Att11]  [Ent60]  | I_60 [Att11]  [Ent60]  | B_60 [Att11]  [Ent60]  | Big_60 [Att11]  [Ent60]  | Small_60 [Att11]  [Ent60]  | Object_60 [Att19]  [Ent3]  | Img_60 [Att21]  | Map_60 [Att24]  [Ent61]  | Label_60 [Att29]  [Ent62]  | Input_60 [Att30]  | Select_60 [Att31]  [Ent90]  | Textarea_60 [Att35]  [Ent2]  | Button_60 [Att39]  [Ent92]  | PCDATA_60 [Att0] B.ByteString
    deriving (Show)

data Ent61 = Script_61 [Att10]  [Ent2]  | Noscript_61 [Att11]  [Ent93]  | Div_61 [Att11]  [Ent94]  | P_61 [Att11]  [Ent60]  | H1_61 [Att11]  [Ent60]  | H2_61 [Att11]  [Ent60]  | H3_61 [Att11]  [Ent60]  | H4_61 [Att11]  [Ent60]  | H5_61 [Att11]  [Ent60]  | H6_61 [Att11]  [Ent60]  | Ul_61 [Att11]  [Ent95]  | Ol_61 [Att11]  [Ent95]  | Dl_61 [Att11]  [Ent96]  | Address_61 [Att11]  [Ent60]  | Hr_61 [Att11]  | Pre_61 [Att11]  [Ent97]  | Blockquote_61 [Att13]  [Ent93]  | Ins_61 [Att14]  [Ent94]  | Del_61 [Att14]  [Ent94]  | Area_61 [Att26]  | Form_61 [Att27]  [Ent98]  | Fieldset_61 [Att11]  [Ent133]  | Table_61 [Att40]  [Ent134] 
    deriving (Show)

data Ent62 = Script_62 [Att10]  [Ent63]  | Ins_62 [Att14]  [Ent64]  | Del_62 [Att14]  [Ent64]  | A_62 [Att15]  [Ent29]  | Span_62 [Att11]  [Ent62]  | Bdo_62 [Att11]  [Ent62]  | Br_62 [Att18]  | Em_62 [Att11]  [Ent62]  | Strong_62 [Att11]  [Ent62]  | Dfn_62 [Att11]  [Ent62]  | Code_62 [Att11]  [Ent62]  | Samp_62 [Att11]  [Ent62]  | Kbd_62 [Att11]  [Ent62]  | Var_62 [Att11]  [Ent62]  | Cite_62 [Att11]  [Ent62]  | Abbr_62 [Att11]  [Ent62]  | Acronym_62 [Att11]  [Ent62]  | Q_62 [Att13]  [Ent62]  | Sub_62 [Att11]  [Ent62]  | Sup_62 [Att11]  [Ent62]  | Tt_62 [Att11]  [Ent62]  | I_62 [Att11]  [Ent62]  | B_62 [Att11]  [Ent62]  | Big_62 [Att11]  [Ent62]  | Small_62 [Att11]  [Ent62]  | Object_62 [Att19]  [Ent85]  | Img_62 [Att21]  | Map_62 [Att24]  [Ent86]  | Input_62 [Att30]  | Select_62 [Att31]  [Ent87]  | Textarea_62 [Att35]  [Ent63]  | Button_62 [Att39]  [Ent89]  | PCDATA_62 [Att0] B.ByteString
    deriving (Show)

data Ent63 = PCDATA_63 [Att0] B.ByteString
    deriving (Show)

data Ent64 = Script_64 [Att10]  [Ent63]  | Noscript_64 [Att11]  [Ent65]  | Div_64 [Att11]  [Ent64]  | P_64 [Att11]  [Ent62]  | H1_64 [Att11]  [Ent62]  | H2_64 [Att11]  [Ent62]  | H3_64 [Att11]  [Ent62]  | H4_64 [Att11]  [Ent62]  | H5_64 [Att11]  [Ent62]  | H6_64 [Att11]  [Ent62]  | Ul_64 [Att11]  [Ent66]  | Ol_64 [Att11]  [Ent66]  | Dl_64 [Att11]  [Ent67]  | Address_64 [Att11]  [Ent62]  | Hr_64 [Att11]  | Pre_64 [Att11]  [Ent68]  | Blockquote_64 [Att13]  [Ent65]  | Ins_64 [Att14]  [Ent64]  | Del_64 [Att14]  [Ent64]  | A_64 [Att15]  [Ent29]  | Span_64 [Att11]  [Ent62]  | Bdo_64 [Att11]  [Ent62]  | Br_64 [Att18]  | Em_64 [Att11]  [Ent62]  | Strong_64 [Att11]  [Ent62]  | Dfn_64 [Att11]  [Ent62]  | Code_64 [Att11]  [Ent62]  | Samp_64 [Att11]  [Ent62]  | Kbd_64 [Att11]  [Ent62]  | Var_64 [Att11]  [Ent62]  | Cite_64 [Att11]  [Ent62]  | Abbr_64 [Att11]  [Ent62]  | Acronym_64 [Att11]  [Ent62]  | Q_64 [Att13]  [Ent62]  | Sub_64 [Att11]  [Ent62]  | Sup_64 [Att11]  [Ent62]  | Tt_64 [Att11]  [Ent62]  | I_64 [Att11]  [Ent62]  | B_64 [Att11]  [Ent62]  | Big_64 [Att11]  [Ent62]  | Small_64 [Att11]  [Ent62]  | Object_64 [Att19]  [Ent85]  | Img_64 [Att21]  | Map_64 [Att24]  [Ent86]  | Form_64 [Att27]  [Ent69]  | Input_64 [Att30]  | Select_64 [Att31]  [Ent87]  | Textarea_64 [Att35]  [Ent63]  | Fieldset_64 [Att11]  [Ent80]  | Button_64 [Att39]  [Ent89]  | Table_64 [Att40]  [Ent81]  | PCDATA_64 [Att0] B.ByteString
    deriving (Show)

data Ent65 = Script_65 [Att10]  [Ent63]  | Noscript_65 [Att11]  [Ent65]  | Div_65 [Att11]  [Ent64]  | P_65 [Att11]  [Ent62]  | H1_65 [Att11]  [Ent62]  | H2_65 [Att11]  [Ent62]  | H3_65 [Att11]  [Ent62]  | H4_65 [Att11]  [Ent62]  | H5_65 [Att11]  [Ent62]  | H6_65 [Att11]  [Ent62]  | Ul_65 [Att11]  [Ent66]  | Ol_65 [Att11]  [Ent66]  | Dl_65 [Att11]  [Ent67]  | Address_65 [Att11]  [Ent62]  | Hr_65 [Att11]  | Pre_65 [Att11]  [Ent68]  | Blockquote_65 [Att13]  [Ent65]  | Ins_65 [Att14]  [Ent64]  | Del_65 [Att14]  [Ent64]  | Form_65 [Att27]  [Ent69]  | Fieldset_65 [Att11]  [Ent80]  | Table_65 [Att40]  [Ent81] 
    deriving (Show)

data Ent66 = Li_66 [Att11]  [Ent64] 
    deriving (Show)

data Ent67 = Dt_67 [Att11]  [Ent62]  | Dd_67 [Att11]  [Ent64] 
    deriving (Show)

data Ent68 = Script_68 [Att10]  [Ent63]  | Ins_68 [Att14]  [Ent64]  | Del_68 [Att14]  [Ent64]  | A_68 [Att15]  [Ent29]  | Span_68 [Att11]  [Ent62]  | Bdo_68 [Att11]  [Ent62]  | Br_68 [Att18]  | Em_68 [Att11]  [Ent62]  | Strong_68 [Att11]  [Ent62]  | Dfn_68 [Att11]  [Ent62]  | Code_68 [Att11]  [Ent62]  | Samp_68 [Att11]  [Ent62]  | Kbd_68 [Att11]  [Ent62]  | Var_68 [Att11]  [Ent62]  | Cite_68 [Att11]  [Ent62]  | Abbr_68 [Att11]  [Ent62]  | Acronym_68 [Att11]  [Ent62]  | Q_68 [Att13]  [Ent62]  | Sub_68 [Att11]  [Ent62]  | Sup_68 [Att11]  [Ent62]  | Tt_68 [Att11]  [Ent62]  | I_68 [Att11]  [Ent62]  | B_68 [Att11]  [Ent62]  | Big_68 [Att11]  [Ent62]  | Small_68 [Att11]  [Ent62]  | Map_68 [Att24]  [Ent86]  | Input_68 [Att30]  | Select_68 [Att31]  [Ent87]  | Textarea_68 [Att35]  [Ent63]  | Button_68 [Att39]  [Ent89]  | PCDATA_68 [Att0] B.ByteString
    deriving (Show)

data Ent69 = Script_69 [Att10]  [Ent116]  | Noscript_69 [Att11]  [Ent69]  | Div_69 [Att11]  [Ent70]  | P_69 [Att11]  [Ent71]  | H1_69 [Att11]  [Ent71]  | H2_69 [Att11]  [Ent71]  | H3_69 [Att11]  [Ent71]  | H4_69 [Att11]  [Ent71]  | H5_69 [Att11]  [Ent71]  | H6_69 [Att11]  [Ent71]  | Ul_69 [Att11]  [Ent72]  | Ol_69 [Att11]  [Ent72]  | Dl_69 [Att11]  [Ent73]  | Address_69 [Att11]  [Ent71]  | Hr_69 [Att11]  | Pre_69 [Att11]  [Ent74]  | Blockquote_69 [Att13]  [Ent69]  | Ins_69 [Att14]  [Ent70]  | Del_69 [Att14]  [Ent70]  | Fieldset_69 [Att11]  [Ent75]  | Table_69 [Att40]  [Ent76] 
    deriving (Show)

data Ent70 = Script_70 [Att10]  [Ent116]  | Noscript_70 [Att11]  [Ent69]  | Div_70 [Att11]  [Ent70]  | P_70 [Att11]  [Ent71]  | H1_70 [Att11]  [Ent71]  | H2_70 [Att11]  [Ent71]  | H3_70 [Att11]  [Ent71]  | H4_70 [Att11]  [Ent71]  | H5_70 [Att11]  [Ent71]  | H6_70 [Att11]  [Ent71]  | Ul_70 [Att11]  [Ent72]  | Ol_70 [Att11]  [Ent72]  | Dl_70 [Att11]  [Ent73]  | Address_70 [Att11]  [Ent71]  | Hr_70 [Att11]  | Pre_70 [Att11]  [Ent74]  | Blockquote_70 [Att13]  [Ent69]  | Ins_70 [Att14]  [Ent70]  | Del_70 [Att14]  [Ent70]  | A_70 [Att15]  [Ent38]  | Span_70 [Att11]  [Ent71]  | Bdo_70 [Att11]  [Ent71]  | Br_70 [Att18]  | Em_70 [Att11]  [Ent71]  | Strong_70 [Att11]  [Ent71]  | Dfn_70 [Att11]  [Ent71]  | Code_70 [Att11]  [Ent71]  | Samp_70 [Att11]  [Ent71]  | Kbd_70 [Att11]  [Ent71]  | Var_70 [Att11]  [Ent71]  | Cite_70 [Att11]  [Ent71]  | Abbr_70 [Att11]  [Ent71]  | Acronym_70 [Att11]  [Ent71]  | Q_70 [Att13]  [Ent71]  | Sub_70 [Att11]  [Ent71]  | Sup_70 [Att11]  [Ent71]  | Tt_70 [Att11]  [Ent71]  | I_70 [Att11]  [Ent71]  | B_70 [Att11]  [Ent71]  | Big_70 [Att11]  [Ent71]  | Small_70 [Att11]  [Ent71]  | Object_70 [Att19]  [Ent117]  | Img_70 [Att21]  | Map_70 [Att24]  [Ent118]  | Input_70 [Att30]  | Select_70 [Att31]  [Ent119]  | Textarea_70 [Att35]  [Ent116]  | Fieldset_70 [Att11]  [Ent75]  | Button_70 [Att39]  [Ent121]  | Table_70 [Att40]  [Ent76]  | PCDATA_70 [Att0] B.ByteString
    deriving (Show)

data Ent71 = Script_71 [Att10]  [Ent116]  | Ins_71 [Att14]  [Ent70]  | Del_71 [Att14]  [Ent70]  | A_71 [Att15]  [Ent38]  | Span_71 [Att11]  [Ent71]  | Bdo_71 [Att11]  [Ent71]  | Br_71 [Att18]  | Em_71 [Att11]  [Ent71]  | Strong_71 [Att11]  [Ent71]  | Dfn_71 [Att11]  [Ent71]  | Code_71 [Att11]  [Ent71]  | Samp_71 [Att11]  [Ent71]  | Kbd_71 [Att11]  [Ent71]  | Var_71 [Att11]  [Ent71]  | Cite_71 [Att11]  [Ent71]  | Abbr_71 [Att11]  [Ent71]  | Acronym_71 [Att11]  [Ent71]  | Q_71 [Att13]  [Ent71]  | Sub_71 [Att11]  [Ent71]  | Sup_71 [Att11]  [Ent71]  | Tt_71 [Att11]  [Ent71]  | I_71 [Att11]  [Ent71]  | B_71 [Att11]  [Ent71]  | Big_71 [Att11]  [Ent71]  | Small_71 [Att11]  [Ent71]  | Object_71 [Att19]  [Ent117]  | Img_71 [Att21]  | Map_71 [Att24]  [Ent118]  | Input_71 [Att30]  | Select_71 [Att31]  [Ent119]  | Textarea_71 [Att35]  [Ent116]  | Button_71 [Att39]  [Ent121]  | PCDATA_71 [Att0] B.ByteString
    deriving (Show)

data Ent72 = Li_72 [Att11]  [Ent70] 
    deriving (Show)

data Ent73 = Dt_73 [Att11]  [Ent71]  | Dd_73 [Att11]  [Ent70] 
    deriving (Show)

data Ent74 = Script_74 [Att10]  [Ent116]  | Ins_74 [Att14]  [Ent70]  | Del_74 [Att14]  [Ent70]  | A_74 [Att15]  [Ent38]  | Span_74 [Att11]  [Ent71]  | Bdo_74 [Att11]  [Ent71]  | Br_74 [Att18]  | Em_74 [Att11]  [Ent71]  | Strong_74 [Att11]  [Ent71]  | Dfn_74 [Att11]  [Ent71]  | Code_74 [Att11]  [Ent71]  | Samp_74 [Att11]  [Ent71]  | Kbd_74 [Att11]  [Ent71]  | Var_74 [Att11]  [Ent71]  | Cite_74 [Att11]  [Ent71]  | Abbr_74 [Att11]  [Ent71]  | Acronym_74 [Att11]  [Ent71]  | Q_74 [Att13]  [Ent71]  | Sub_74 [Att11]  [Ent71]  | Sup_74 [Att11]  [Ent71]  | Tt_74 [Att11]  [Ent71]  | I_74 [Att11]  [Ent71]  | B_74 [Att11]  [Ent71]  | Big_74 [Att11]  [Ent71]  | Small_74 [Att11]  [Ent71]  | Map_74 [Att24]  [Ent118]  | Input_74 [Att30]  | Select_74 [Att31]  [Ent119]  | Textarea_74 [Att35]  [Ent116]  | Button_74 [Att39]  [Ent121]  | PCDATA_74 [Att0] B.ByteString
    deriving (Show)

data Ent75 = Script_75 [Att10]  [Ent116]  | Noscript_75 [Att11]  [Ent69]  | Div_75 [Att11]  [Ent70]  | P_75 [Att11]  [Ent71]  | H1_75 [Att11]  [Ent71]  | H2_75 [Att11]  [Ent71]  | H3_75 [Att11]  [Ent71]  | H4_75 [Att11]  [Ent71]  | H5_75 [Att11]  [Ent71]  | H6_75 [Att11]  [Ent71]  | Ul_75 [Att11]  [Ent72]  | Ol_75 [Att11]  [Ent72]  | Dl_75 [Att11]  [Ent73]  | Address_75 [Att11]  [Ent71]  | Hr_75 [Att11]  | Pre_75 [Att11]  [Ent74]  | Blockquote_75 [Att13]  [Ent69]  | Ins_75 [Att14]  [Ent70]  | Del_75 [Att14]  [Ent70]  | A_75 [Att15]  [Ent38]  | Span_75 [Att11]  [Ent71]  | Bdo_75 [Att11]  [Ent71]  | Br_75 [Att18]  | Em_75 [Att11]  [Ent71]  | Strong_75 [Att11]  [Ent71]  | Dfn_75 [Att11]  [Ent71]  | Code_75 [Att11]  [Ent71]  | Samp_75 [Att11]  [Ent71]  | Kbd_75 [Att11]  [Ent71]  | Var_75 [Att11]  [Ent71]  | Cite_75 [Att11]  [Ent71]  | Abbr_75 [Att11]  [Ent71]  | Acronym_75 [Att11]  [Ent71]  | Q_75 [Att13]  [Ent71]  | Sub_75 [Att11]  [Ent71]  | Sup_75 [Att11]  [Ent71]  | Tt_75 [Att11]  [Ent71]  | I_75 [Att11]  [Ent71]  | B_75 [Att11]  [Ent71]  | Big_75 [Att11]  [Ent71]  | Small_75 [Att11]  [Ent71]  | Object_75 [Att19]  [Ent117]  | Img_75 [Att21]  | Map_75 [Att24]  [Ent118]  | Input_75 [Att30]  | Select_75 [Att31]  [Ent119]  | Textarea_75 [Att35]  [Ent116]  | Fieldset_75 [Att11]  [Ent75]  | Legend_75 [Att38]  [Ent71]  | Button_75 [Att39]  [Ent121]  | Table_75 [Att40]  [Ent76]  | PCDATA_75 [Att0] B.ByteString
    deriving (Show)

data Ent76 = Caption_76 [Att11]  [Ent71]  | Thead_76 [Att41]  [Ent77]  | Tfoot_76 [Att41]  [Ent77]  | Tbody_76 [Att41]  [Ent77]  | Colgroup_76 [Att42]  [Ent78]  | Col_76 [Att42]  | Tr_76 [Att41]  [Ent79] 
    deriving (Show)

data Ent77 = Tr_77 [Att41]  [Ent79] 
    deriving (Show)

data Ent78 = Col_78 [Att42] 
    deriving (Show)

data Ent79 = Th_79 [Att43]  [Ent70]  | Td_79 [Att43]  [Ent70] 
    deriving (Show)

data Ent80 = Script_80 [Att10]  [Ent63]  | Noscript_80 [Att11]  [Ent65]  | Div_80 [Att11]  [Ent64]  | P_80 [Att11]  [Ent62]  | H1_80 [Att11]  [Ent62]  | H2_80 [Att11]  [Ent62]  | H3_80 [Att11]  [Ent62]  | H4_80 [Att11]  [Ent62]  | H5_80 [Att11]  [Ent62]  | H6_80 [Att11]  [Ent62]  | Ul_80 [Att11]  [Ent66]  | Ol_80 [Att11]  [Ent66]  | Dl_80 [Att11]  [Ent67]  | Address_80 [Att11]  [Ent62]  | Hr_80 [Att11]  | Pre_80 [Att11]  [Ent68]  | Blockquote_80 [Att13]  [Ent65]  | Ins_80 [Att14]  [Ent64]  | Del_80 [Att14]  [Ent64]  | A_80 [Att15]  [Ent29]  | Span_80 [Att11]  [Ent62]  | Bdo_80 [Att11]  [Ent62]  | Br_80 [Att18]  | Em_80 [Att11]  [Ent62]  | Strong_80 [Att11]  [Ent62]  | Dfn_80 [Att11]  [Ent62]  | Code_80 [Att11]  [Ent62]  | Samp_80 [Att11]  [Ent62]  | Kbd_80 [Att11]  [Ent62]  | Var_80 [Att11]  [Ent62]  | Cite_80 [Att11]  [Ent62]  | Abbr_80 [Att11]  [Ent62]  | Acronym_80 [Att11]  [Ent62]  | Q_80 [Att13]  [Ent62]  | Sub_80 [Att11]  [Ent62]  | Sup_80 [Att11]  [Ent62]  | Tt_80 [Att11]  [Ent62]  | I_80 [Att11]  [Ent62]  | B_80 [Att11]  [Ent62]  | Big_80 [Att11]  [Ent62]  | Small_80 [Att11]  [Ent62]  | Object_80 [Att19]  [Ent85]  | Img_80 [Att21]  | Map_80 [Att24]  [Ent86]  | Form_80 [Att27]  [Ent69]  | Input_80 [Att30]  | Select_80 [Att31]  [Ent87]  | Textarea_80 [Att35]  [Ent63]  | Fieldset_80 [Att11]  [Ent80]  | Legend_80 [Att38]  [Ent62]  | Button_80 [Att39]  [Ent89]  | Table_80 [Att40]  [Ent81]  | PCDATA_80 [Att0] B.ByteString
    deriving (Show)

data Ent81 = Caption_81 [Att11]  [Ent62]  | Thead_81 [Att41]  [Ent82]  | Tfoot_81 [Att41]  [Ent82]  | Tbody_81 [Att41]  [Ent82]  | Colgroup_81 [Att42]  [Ent83]  | Col_81 [Att42]  | Tr_81 [Att41]  [Ent84] 
    deriving (Show)

data Ent82 = Tr_82 [Att41]  [Ent84] 
    deriving (Show)

data Ent83 = Col_83 [Att42] 
    deriving (Show)

data Ent84 = Th_84 [Att43]  [Ent64]  | Td_84 [Att43]  [Ent64] 
    deriving (Show)

data Ent85 = Script_85 [Att10]  [Ent63]  | Noscript_85 [Att11]  [Ent65]  | Div_85 [Att11]  [Ent64]  | P_85 [Att11]  [Ent62]  | H1_85 [Att11]  [Ent62]  | H2_85 [Att11]  [Ent62]  | H3_85 [Att11]  [Ent62]  | H4_85 [Att11]  [Ent62]  | H5_85 [Att11]  [Ent62]  | H6_85 [Att11]  [Ent62]  | Ul_85 [Att11]  [Ent66]  | Ol_85 [Att11]  [Ent66]  | Dl_85 [Att11]  [Ent67]  | Address_85 [Att11]  [Ent62]  | Hr_85 [Att11]  | Pre_85 [Att11]  [Ent68]  | Blockquote_85 [Att13]  [Ent65]  | Ins_85 [Att14]  [Ent64]  | Del_85 [Att14]  [Ent64]  | A_85 [Att15]  [Ent29]  | Span_85 [Att11]  [Ent62]  | Bdo_85 [Att11]  [Ent62]  | Br_85 [Att18]  | Em_85 [Att11]  [Ent62]  | Strong_85 [Att11]  [Ent62]  | Dfn_85 [Att11]  [Ent62]  | Code_85 [Att11]  [Ent62]  | Samp_85 [Att11]  [Ent62]  | Kbd_85 [Att11]  [Ent62]  | Var_85 [Att11]  [Ent62]  | Cite_85 [Att11]  [Ent62]  | Abbr_85 [Att11]  [Ent62]  | Acronym_85 [Att11]  [Ent62]  | Q_85 [Att13]  [Ent62]  | Sub_85 [Att11]  [Ent62]  | Sup_85 [Att11]  [Ent62]  | Tt_85 [Att11]  [Ent62]  | I_85 [Att11]  [Ent62]  | B_85 [Att11]  [Ent62]  | Big_85 [Att11]  [Ent62]  | Small_85 [Att11]  [Ent62]  | Object_85 [Att19]  [Ent85]  | Param_85 [Att20]  | Img_85 [Att21]  | Map_85 [Att24]  [Ent86]  | Form_85 [Att27]  [Ent69]  | Input_85 [Att30]  | Select_85 [Att31]  [Ent87]  | Textarea_85 [Att35]  [Ent63]  | Fieldset_85 [Att11]  [Ent80]  | Button_85 [Att39]  [Ent89]  | Table_85 [Att40]  [Ent81]  | PCDATA_85 [Att0] B.ByteString
    deriving (Show)

data Ent86 = Script_86 [Att10]  [Ent63]  | Noscript_86 [Att11]  [Ent65]  | Div_86 [Att11]  [Ent64]  | P_86 [Att11]  [Ent62]  | H1_86 [Att11]  [Ent62]  | H2_86 [Att11]  [Ent62]  | H3_86 [Att11]  [Ent62]  | H4_86 [Att11]  [Ent62]  | H5_86 [Att11]  [Ent62]  | H6_86 [Att11]  [Ent62]  | Ul_86 [Att11]  [Ent66]  | Ol_86 [Att11]  [Ent66]  | Dl_86 [Att11]  [Ent67]  | Address_86 [Att11]  [Ent62]  | Hr_86 [Att11]  | Pre_86 [Att11]  [Ent68]  | Blockquote_86 [Att13]  [Ent65]  | Ins_86 [Att14]  [Ent64]  | Del_86 [Att14]  [Ent64]  | Area_86 [Att26]  | Form_86 [Att27]  [Ent69]  | Fieldset_86 [Att11]  [Ent80]  | Table_86 [Att40]  [Ent81] 
    deriving (Show)

data Ent87 = Optgroup_87 [Att32]  [Ent88]  | Option_87 [Att34]  [Ent63] 
    deriving (Show)

data Ent88 = Option_88 [Att34]  [Ent63] 
    deriving (Show)

data Ent89 = Script_89 [Att10]  [Ent63]  | Noscript_89 [Att11]  [Ent65]  | Div_89 [Att11]  [Ent64]  | P_89 [Att11]  [Ent62]  | H1_89 [Att11]  [Ent62]  | H2_89 [Att11]  [Ent62]  | H3_89 [Att11]  [Ent62]  | H4_89 [Att11]  [Ent62]  | H5_89 [Att11]  [Ent62]  | H6_89 [Att11]  [Ent62]  | Ul_89 [Att11]  [Ent66]  | Ol_89 [Att11]  [Ent66]  | Dl_89 [Att11]  [Ent67]  | Address_89 [Att11]  [Ent62]  | Hr_89 [Att11]  | Pre_89 [Att11]  [Ent68]  | Blockquote_89 [Att13]  [Ent65]  | Ins_89 [Att14]  [Ent64]  | Del_89 [Att14]  [Ent64]  | Span_89 [Att11]  [Ent62]  | Bdo_89 [Att11]  [Ent62]  | Br_89 [Att18]  | Em_89 [Att11]  [Ent62]  | Strong_89 [Att11]  [Ent62]  | Dfn_89 [Att11]  [Ent62]  | Code_89 [Att11]  [Ent62]  | Samp_89 [Att11]  [Ent62]  | Kbd_89 [Att11]  [Ent62]  | Var_89 [Att11]  [Ent62]  | Cite_89 [Att11]  [Ent62]  | Abbr_89 [Att11]  [Ent62]  | Acronym_89 [Att11]  [Ent62]  | Q_89 [Att13]  [Ent62]  | Sub_89 [Att11]  [Ent62]  | Sup_89 [Att11]  [Ent62]  | Tt_89 [Att11]  [Ent62]  | I_89 [Att11]  [Ent62]  | B_89 [Att11]  [Ent62]  | Big_89 [Att11]  [Ent62]  | Small_89 [Att11]  [Ent62]  | Object_89 [Att19]  [Ent85]  | Img_89 [Att21]  | Map_89 [Att24]  [Ent86]  | Table_89 [Att40]  [Ent81]  | PCDATA_89 [Att0] B.ByteString
    deriving (Show)

data Ent90 = Optgroup_90 [Att32]  [Ent91]  | Option_90 [Att34]  [Ent2] 
    deriving (Show)

data Ent91 = Option_91 [Att34]  [Ent2] 
    deriving (Show)

data Ent92 = Script_92 [Att10]  [Ent2]  | Noscript_92 [Att11]  [Ent93]  | Div_92 [Att11]  [Ent94]  | P_92 [Att11]  [Ent60]  | H1_92 [Att11]  [Ent60]  | H2_92 [Att11]  [Ent60]  | H3_92 [Att11]  [Ent60]  | H4_92 [Att11]  [Ent60]  | H5_92 [Att11]  [Ent60]  | H6_92 [Att11]  [Ent60]  | Ul_92 [Att11]  [Ent95]  | Ol_92 [Att11]  [Ent95]  | Dl_92 [Att11]  [Ent96]  | Address_92 [Att11]  [Ent60]  | Hr_92 [Att11]  | Pre_92 [Att11]  [Ent97]  | Blockquote_92 [Att13]  [Ent93]  | Ins_92 [Att14]  [Ent94]  | Del_92 [Att14]  [Ent94]  | Span_92 [Att11]  [Ent60]  | Bdo_92 [Att11]  [Ent60]  | Br_92 [Att18]  | Em_92 [Att11]  [Ent60]  | Strong_92 [Att11]  [Ent60]  | Dfn_92 [Att11]  [Ent60]  | Code_92 [Att11]  [Ent60]  | Samp_92 [Att11]  [Ent60]  | Kbd_92 [Att11]  [Ent60]  | Var_92 [Att11]  [Ent60]  | Cite_92 [Att11]  [Ent60]  | Abbr_92 [Att11]  [Ent60]  | Acronym_92 [Att11]  [Ent60]  | Q_92 [Att13]  [Ent60]  | Sub_92 [Att11]  [Ent60]  | Sup_92 [Att11]  [Ent60]  | Tt_92 [Att11]  [Ent60]  | I_92 [Att11]  [Ent60]  | B_92 [Att11]  [Ent60]  | Big_92 [Att11]  [Ent60]  | Small_92 [Att11]  [Ent60]  | Object_92 [Att19]  [Ent3]  | Img_92 [Att21]  | Map_92 [Att24]  [Ent61]  | Table_92 [Att40]  [Ent134]  | PCDATA_92 [Att0] B.ByteString
    deriving (Show)

data Ent93 = Script_93 [Att10]  [Ent2]  | Noscript_93 [Att11]  [Ent93]  | Div_93 [Att11]  [Ent94]  | P_93 [Att11]  [Ent60]  | H1_93 [Att11]  [Ent60]  | H2_93 [Att11]  [Ent60]  | H3_93 [Att11]  [Ent60]  | H4_93 [Att11]  [Ent60]  | H5_93 [Att11]  [Ent60]  | H6_93 [Att11]  [Ent60]  | Ul_93 [Att11]  [Ent95]  | Ol_93 [Att11]  [Ent95]  | Dl_93 [Att11]  [Ent96]  | Address_93 [Att11]  [Ent60]  | Hr_93 [Att11]  | Pre_93 [Att11]  [Ent97]  | Blockquote_93 [Att13]  [Ent93]  | Ins_93 [Att14]  [Ent94]  | Del_93 [Att14]  [Ent94]  | Form_93 [Att27]  [Ent98]  | Fieldset_93 [Att11]  [Ent133]  | Table_93 [Att40]  [Ent134] 
    deriving (Show)

data Ent94 = Script_94 [Att10]  [Ent2]  | Noscript_94 [Att11]  [Ent93]  | Div_94 [Att11]  [Ent94]  | P_94 [Att11]  [Ent60]  | H1_94 [Att11]  [Ent60]  | H2_94 [Att11]  [Ent60]  | H3_94 [Att11]  [Ent60]  | H4_94 [Att11]  [Ent60]  | H5_94 [Att11]  [Ent60]  | H6_94 [Att11]  [Ent60]  | Ul_94 [Att11]  [Ent95]  | Ol_94 [Att11]  [Ent95]  | Dl_94 [Att11]  [Ent96]  | Address_94 [Att11]  [Ent60]  | Hr_94 [Att11]  | Pre_94 [Att11]  [Ent97]  | Blockquote_94 [Att13]  [Ent93]  | Ins_94 [Att14]  [Ent94]  | Del_94 [Att14]  [Ent94]  | A_94 [Att15]  [Ent4]  | Span_94 [Att11]  [Ent60]  | Bdo_94 [Att11]  [Ent60]  | Br_94 [Att18]  | Em_94 [Att11]  [Ent60]  | Strong_94 [Att11]  [Ent60]  | Dfn_94 [Att11]  [Ent60]  | Code_94 [Att11]  [Ent60]  | Samp_94 [Att11]  [Ent60]  | Kbd_94 [Att11]  [Ent60]  | Var_94 [Att11]  [Ent60]  | Cite_94 [Att11]  [Ent60]  | Abbr_94 [Att11]  [Ent60]  | Acronym_94 [Att11]  [Ent60]  | Q_94 [Att13]  [Ent60]  | Sub_94 [Att11]  [Ent60]  | Sup_94 [Att11]  [Ent60]  | Tt_94 [Att11]  [Ent60]  | I_94 [Att11]  [Ent60]  | B_94 [Att11]  [Ent60]  | Big_94 [Att11]  [Ent60]  | Small_94 [Att11]  [Ent60]  | Object_94 [Att19]  [Ent3]  | Img_94 [Att21]  | Map_94 [Att24]  [Ent61]  | Form_94 [Att27]  [Ent98]  | Label_94 [Att29]  [Ent62]  | Input_94 [Att30]  | Select_94 [Att31]  [Ent90]  | Textarea_94 [Att35]  [Ent2]  | Fieldset_94 [Att11]  [Ent133]  | Button_94 [Att39]  [Ent92]  | Table_94 [Att40]  [Ent134]  | PCDATA_94 [Att0] B.ByteString
    deriving (Show)

data Ent95 = Li_95 [Att11]  [Ent94] 
    deriving (Show)

data Ent96 = Dt_96 [Att11]  [Ent60]  | Dd_96 [Att11]  [Ent94] 
    deriving (Show)

data Ent97 = Script_97 [Att10]  [Ent2]  | Ins_97 [Att14]  [Ent94]  | Del_97 [Att14]  [Ent94]  | A_97 [Att15]  [Ent4]  | Span_97 [Att11]  [Ent60]  | Bdo_97 [Att11]  [Ent60]  | Br_97 [Att18]  | Em_97 [Att11]  [Ent60]  | Strong_97 [Att11]  [Ent60]  | Dfn_97 [Att11]  [Ent60]  | Code_97 [Att11]  [Ent60]  | Samp_97 [Att11]  [Ent60]  | Kbd_97 [Att11]  [Ent60]  | Var_97 [Att11]  [Ent60]  | Cite_97 [Att11]  [Ent60]  | Abbr_97 [Att11]  [Ent60]  | Acronym_97 [Att11]  [Ent60]  | Q_97 [Att13]  [Ent60]  | Sub_97 [Att11]  [Ent60]  | Sup_97 [Att11]  [Ent60]  | Tt_97 [Att11]  [Ent60]  | I_97 [Att11]  [Ent60]  | B_97 [Att11]  [Ent60]  | Big_97 [Att11]  [Ent60]  | Small_97 [Att11]  [Ent60]  | Map_97 [Att24]  [Ent61]  | Label_97 [Att29]  [Ent62]  | Input_97 [Att30]  | Select_97 [Att31]  [Ent90]  | Textarea_97 [Att35]  [Ent2]  | Button_97 [Att39]  [Ent92]  | PCDATA_97 [Att0] B.ByteString
    deriving (Show)

data Ent98 = Script_98 [Att10]  [Ent99]  | Noscript_98 [Att11]  [Ent98]  | Div_98 [Att11]  [Ent100]  | P_98 [Att11]  [Ent113]  | H1_98 [Att11]  [Ent113]  | H2_98 [Att11]  [Ent113]  | H3_98 [Att11]  [Ent113]  | H4_98 [Att11]  [Ent113]  | H5_98 [Att11]  [Ent113]  | H6_98 [Att11]  [Ent113]  | Ul_98 [Att11]  [Ent125]  | Ol_98 [Att11]  [Ent125]  | Dl_98 [Att11]  [Ent126]  | Address_98 [Att11]  [Ent113]  | Hr_98 [Att11]  | Pre_98 [Att11]  [Ent127]  | Blockquote_98 [Att13]  [Ent98]  | Ins_98 [Att14]  [Ent100]  | Del_98 [Att14]  [Ent100]  | Fieldset_98 [Att11]  [Ent128]  | Table_98 [Att40]  [Ent129] 
    deriving (Show)

data Ent99 = PCDATA_99 [Att0] B.ByteString
    deriving (Show)

data Ent100 = Script_100 [Att10]  [Ent99]  | Noscript_100 [Att11]  [Ent98]  | Div_100 [Att11]  [Ent100]  | P_100 [Att11]  [Ent113]  | H1_100 [Att11]  [Ent113]  | H2_100 [Att11]  [Ent113]  | H3_100 [Att11]  [Ent113]  | H4_100 [Att11]  [Ent113]  | H5_100 [Att11]  [Ent113]  | H6_100 [Att11]  [Ent113]  | Ul_100 [Att11]  [Ent125]  | Ol_100 [Att11]  [Ent125]  | Dl_100 [Att11]  [Ent126]  | Address_100 [Att11]  [Ent113]  | Hr_100 [Att11]  | Pre_100 [Att11]  [Ent127]  | Blockquote_100 [Att13]  [Ent98]  | Ins_100 [Att14]  [Ent100]  | Del_100 [Att14]  [Ent100]  | A_100 [Att15]  [Ent13]  | Span_100 [Att11]  [Ent113]  | Bdo_100 [Att11]  [Ent113]  | Br_100 [Att18]  | Em_100 [Att11]  [Ent113]  | Strong_100 [Att11]  [Ent113]  | Dfn_100 [Att11]  [Ent113]  | Code_100 [Att11]  [Ent113]  | Samp_100 [Att11]  [Ent113]  | Kbd_100 [Att11]  [Ent113]  | Var_100 [Att11]  [Ent113]  | Cite_100 [Att11]  [Ent113]  | Abbr_100 [Att11]  [Ent113]  | Acronym_100 [Att11]  [Ent113]  | Q_100 [Att13]  [Ent113]  | Sub_100 [Att11]  [Ent113]  | Sup_100 [Att11]  [Ent113]  | Tt_100 [Att11]  [Ent113]  | I_100 [Att11]  [Ent113]  | B_100 [Att11]  [Ent113]  | Big_100 [Att11]  [Ent113]  | Small_100 [Att11]  [Ent113]  | Object_100 [Att19]  [Ent114]  | Img_100 [Att21]  | Map_100 [Att24]  [Ent115]  | Label_100 [Att29]  [Ent71]  | Input_100 [Att30]  | Select_100 [Att31]  [Ent122]  | Textarea_100 [Att35]  [Ent99]  | Fieldset_100 [Att11]  [Ent128]  | Button_100 [Att39]  [Ent124]  | Table_100 [Att40]  [Ent129]  | PCDATA_100 [Att0] B.ByteString
    deriving (Show)

data Ent101 = PCDATA_101 [Att0] B.ByteString
    deriving (Show)

data Ent102 = Script_102 [Att10]  [Ent101]  | Noscript_102 [Att11]  [Ent11]  | Div_102 [Att11]  [Ent12]  | P_102 [Att11]  [Ent13]  | H1_102 [Att11]  [Ent13]  | H2_102 [Att11]  [Ent13]  | H3_102 [Att11]  [Ent13]  | H4_102 [Att11]  [Ent13]  | H5_102 [Att11]  [Ent13]  | H6_102 [Att11]  [Ent13]  | Ul_102 [Att11]  [Ent14]  | Ol_102 [Att11]  [Ent14]  | Dl_102 [Att11]  [Ent15]  | Address_102 [Att11]  [Ent13]  | Hr_102 [Att11]  | Pre_102 [Att11]  [Ent16]  | Blockquote_102 [Att13]  [Ent11]  | Ins_102 [Att14]  [Ent12]  | Del_102 [Att14]  [Ent12]  | Span_102 [Att11]  [Ent13]  | Bdo_102 [Att11]  [Ent13]  | Br_102 [Att18]  | Em_102 [Att11]  [Ent13]  | Strong_102 [Att11]  [Ent13]  | Dfn_102 [Att11]  [Ent13]  | Code_102 [Att11]  [Ent13]  | Samp_102 [Att11]  [Ent13]  | Kbd_102 [Att11]  [Ent13]  | Var_102 [Att11]  [Ent13]  | Cite_102 [Att11]  [Ent13]  | Abbr_102 [Att11]  [Ent13]  | Acronym_102 [Att11]  [Ent13]  | Q_102 [Att13]  [Ent13]  | Sub_102 [Att11]  [Ent13]  | Sup_102 [Att11]  [Ent13]  | Tt_102 [Att11]  [Ent13]  | I_102 [Att11]  [Ent13]  | B_102 [Att11]  [Ent13]  | Big_102 [Att11]  [Ent13]  | Small_102 [Att11]  [Ent13]  | Object_102 [Att19]  [Ent102]  | Param_102 [Att20]  | Img_102 [Att21]  | Map_102 [Att24]  [Ent103]  | Label_102 [Att29]  [Ent38]  | Input_102 [Att30]  | Select_102 [Att31]  [Ent110]  | Textarea_102 [Att35]  [Ent101]  | Fieldset_102 [Att11]  [Ent17]  | Button_102 [Att39]  [Ent112]  | Table_102 [Att40]  [Ent18]  | PCDATA_102 [Att0] B.ByteString
    deriving (Show)

data Ent103 = Script_103 [Att10]  [Ent101]  | Noscript_103 [Att11]  [Ent11]  | Div_103 [Att11]  [Ent12]  | P_103 [Att11]  [Ent13]  | H1_103 [Att11]  [Ent13]  | H2_103 [Att11]  [Ent13]  | H3_103 [Att11]  [Ent13]  | H4_103 [Att11]  [Ent13]  | H5_103 [Att11]  [Ent13]  | H6_103 [Att11]  [Ent13]  | Ul_103 [Att11]  [Ent14]  | Ol_103 [Att11]  [Ent14]  | Dl_103 [Att11]  [Ent15]  | Address_103 [Att11]  [Ent13]  | Hr_103 [Att11]  | Pre_103 [Att11]  [Ent16]  | Blockquote_103 [Att13]  [Ent11]  | Ins_103 [Att14]  [Ent12]  | Del_103 [Att14]  [Ent12]  | Area_103 [Att26]  | Fieldset_103 [Att11]  [Ent17]  | Table_103 [Att40]  [Ent18] 
    deriving (Show)

data Ent104 = PCDATA_104 [Att0] B.ByteString
    deriving (Show)

data Ent105 = Script_105 [Att10]  [Ent104]  | Noscript_105 [Att11]  [Ent36]  | Div_105 [Att11]  [Ent37]  | P_105 [Att11]  [Ent38]  | H1_105 [Att11]  [Ent38]  | H2_105 [Att11]  [Ent38]  | H3_105 [Att11]  [Ent38]  | H4_105 [Att11]  [Ent38]  | H5_105 [Att11]  [Ent38]  | H6_105 [Att11]  [Ent38]  | Ul_105 [Att11]  [Ent39]  | Ol_105 [Att11]  [Ent39]  | Dl_105 [Att11]  [Ent40]  | Address_105 [Att11]  [Ent38]  | Hr_105 [Att11]  | Pre_105 [Att11]  [Ent41]  | Blockquote_105 [Att13]  [Ent36]  | Ins_105 [Att14]  [Ent37]  | Del_105 [Att14]  [Ent37]  | Span_105 [Att11]  [Ent38]  | Bdo_105 [Att11]  [Ent38]  | Br_105 [Att18]  | Em_105 [Att11]  [Ent38]  | Strong_105 [Att11]  [Ent38]  | Dfn_105 [Att11]  [Ent38]  | Code_105 [Att11]  [Ent38]  | Samp_105 [Att11]  [Ent38]  | Kbd_105 [Att11]  [Ent38]  | Var_105 [Att11]  [Ent38]  | Cite_105 [Att11]  [Ent38]  | Abbr_105 [Att11]  [Ent38]  | Acronym_105 [Att11]  [Ent38]  | Q_105 [Att13]  [Ent38]  | Sub_105 [Att11]  [Ent38]  | Sup_105 [Att11]  [Ent38]  | Tt_105 [Att11]  [Ent38]  | I_105 [Att11]  [Ent38]  | B_105 [Att11]  [Ent38]  | Big_105 [Att11]  [Ent38]  | Small_105 [Att11]  [Ent38]  | Object_105 [Att19]  [Ent105]  | Param_105 [Att20]  | Img_105 [Att21]  | Map_105 [Att24]  [Ent106]  | Input_105 [Att30]  | Select_105 [Att31]  [Ent107]  | Textarea_105 [Att35]  [Ent104]  | Fieldset_105 [Att11]  [Ent42]  | Button_105 [Att39]  [Ent109]  | Table_105 [Att40]  [Ent43]  | PCDATA_105 [Att0] B.ByteString
    deriving (Show)

data Ent106 = Script_106 [Att10]  [Ent104]  | Noscript_106 [Att11]  [Ent36]  | Div_106 [Att11]  [Ent37]  | P_106 [Att11]  [Ent38]  | H1_106 [Att11]  [Ent38]  | H2_106 [Att11]  [Ent38]  | H3_106 [Att11]  [Ent38]  | H4_106 [Att11]  [Ent38]  | H5_106 [Att11]  [Ent38]  | H6_106 [Att11]  [Ent38]  | Ul_106 [Att11]  [Ent39]  | Ol_106 [Att11]  [Ent39]  | Dl_106 [Att11]  [Ent40]  | Address_106 [Att11]  [Ent38]  | Hr_106 [Att11]  | Pre_106 [Att11]  [Ent41]  | Blockquote_106 [Att13]  [Ent36]  | Ins_106 [Att14]  [Ent37]  | Del_106 [Att14]  [Ent37]  | Area_106 [Att26]  | Fieldset_106 [Att11]  [Ent42]  | Table_106 [Att40]  [Ent43] 
    deriving (Show)

data Ent107 = Optgroup_107 [Att32]  [Ent108]  | Option_107 [Att34]  [Ent104] 
    deriving (Show)

data Ent108 = Option_108 [Att34]  [Ent104] 
    deriving (Show)

data Ent109 = Script_109 [Att10]  [Ent104]  | Noscript_109 [Att11]  [Ent36]  | Div_109 [Att11]  [Ent37]  | P_109 [Att11]  [Ent38]  | H1_109 [Att11]  [Ent38]  | H2_109 [Att11]  [Ent38]  | H3_109 [Att11]  [Ent38]  | H4_109 [Att11]  [Ent38]  | H5_109 [Att11]  [Ent38]  | H6_109 [Att11]  [Ent38]  | Ul_109 [Att11]  [Ent39]  | Ol_109 [Att11]  [Ent39]  | Dl_109 [Att11]  [Ent40]  | Address_109 [Att11]  [Ent38]  | Hr_109 [Att11]  | Pre_109 [Att11]  [Ent41]  | Blockquote_109 [Att13]  [Ent36]  | Ins_109 [Att14]  [Ent37]  | Del_109 [Att14]  [Ent37]  | Span_109 [Att11]  [Ent38]  | Bdo_109 [Att11]  [Ent38]  | Br_109 [Att18]  | Em_109 [Att11]  [Ent38]  | Strong_109 [Att11]  [Ent38]  | Dfn_109 [Att11]  [Ent38]  | Code_109 [Att11]  [Ent38]  | Samp_109 [Att11]  [Ent38]  | Kbd_109 [Att11]  [Ent38]  | Var_109 [Att11]  [Ent38]  | Cite_109 [Att11]  [Ent38]  | Abbr_109 [Att11]  [Ent38]  | Acronym_109 [Att11]  [Ent38]  | Q_109 [Att13]  [Ent38]  | Sub_109 [Att11]  [Ent38]  | Sup_109 [Att11]  [Ent38]  | Tt_109 [Att11]  [Ent38]  | I_109 [Att11]  [Ent38]  | B_109 [Att11]  [Ent38]  | Big_109 [Att11]  [Ent38]  | Small_109 [Att11]  [Ent38]  | Object_109 [Att19]  [Ent105]  | Img_109 [Att21]  | Map_109 [Att24]  [Ent106]  | Table_109 [Att40]  [Ent43]  | PCDATA_109 [Att0] B.ByteString
    deriving (Show)

data Ent110 = Optgroup_110 [Att32]  [Ent111]  | Option_110 [Att34]  [Ent101] 
    deriving (Show)

data Ent111 = Option_111 [Att34]  [Ent101] 
    deriving (Show)

data Ent112 = Script_112 [Att10]  [Ent101]  | Noscript_112 [Att11]  [Ent11]  | Div_112 [Att11]  [Ent12]  | P_112 [Att11]  [Ent13]  | H1_112 [Att11]  [Ent13]  | H2_112 [Att11]  [Ent13]  | H3_112 [Att11]  [Ent13]  | H4_112 [Att11]  [Ent13]  | H5_112 [Att11]  [Ent13]  | H6_112 [Att11]  [Ent13]  | Ul_112 [Att11]  [Ent14]  | Ol_112 [Att11]  [Ent14]  | Dl_112 [Att11]  [Ent15]  | Address_112 [Att11]  [Ent13]  | Hr_112 [Att11]  | Pre_112 [Att11]  [Ent16]  | Blockquote_112 [Att13]  [Ent11]  | Ins_112 [Att14]  [Ent12]  | Del_112 [Att14]  [Ent12]  | Span_112 [Att11]  [Ent13]  | Bdo_112 [Att11]  [Ent13]  | Br_112 [Att18]  | Em_112 [Att11]  [Ent13]  | Strong_112 [Att11]  [Ent13]  | Dfn_112 [Att11]  [Ent13]  | Code_112 [Att11]  [Ent13]  | Samp_112 [Att11]  [Ent13]  | Kbd_112 [Att11]  [Ent13]  | Var_112 [Att11]  [Ent13]  | Cite_112 [Att11]  [Ent13]  | Abbr_112 [Att11]  [Ent13]  | Acronym_112 [Att11]  [Ent13]  | Q_112 [Att13]  [Ent13]  | Sub_112 [Att11]  [Ent13]  | Sup_112 [Att11]  [Ent13]  | Tt_112 [Att11]  [Ent13]  | I_112 [Att11]  [Ent13]  | B_112 [Att11]  [Ent13]  | Big_112 [Att11]  [Ent13]  | Small_112 [Att11]  [Ent13]  | Object_112 [Att19]  [Ent102]  | Img_112 [Att21]  | Map_112 [Att24]  [Ent103]  | Table_112 [Att40]  [Ent18]  | PCDATA_112 [Att0] B.ByteString
    deriving (Show)

data Ent113 = Script_113 [Att10]  [Ent99]  | Ins_113 [Att14]  [Ent100]  | Del_113 [Att14]  [Ent100]  | A_113 [Att15]  [Ent13]  | Span_113 [Att11]  [Ent113]  | Bdo_113 [Att11]  [Ent113]  | Br_113 [Att18]  | Em_113 [Att11]  [Ent113]  | Strong_113 [Att11]  [Ent113]  | Dfn_113 [Att11]  [Ent113]  | Code_113 [Att11]  [Ent113]  | Samp_113 [Att11]  [Ent113]  | Kbd_113 [Att11]  [Ent113]  | Var_113 [Att11]  [Ent113]  | Cite_113 [Att11]  [Ent113]  | Abbr_113 [Att11]  [Ent113]  | Acronym_113 [Att11]  [Ent113]  | Q_113 [Att13]  [Ent113]  | Sub_113 [Att11]  [Ent113]  | Sup_113 [Att11]  [Ent113]  | Tt_113 [Att11]  [Ent113]  | I_113 [Att11]  [Ent113]  | B_113 [Att11]  [Ent113]  | Big_113 [Att11]  [Ent113]  | Small_113 [Att11]  [Ent113]  | Object_113 [Att19]  [Ent114]  | Img_113 [Att21]  | Map_113 [Att24]  [Ent115]  | Label_113 [Att29]  [Ent71]  | Input_113 [Att30]  | Select_113 [Att31]  [Ent122]  | Textarea_113 [Att35]  [Ent99]  | Button_113 [Att39]  [Ent124]  | PCDATA_113 [Att0] B.ByteString
    deriving (Show)

data Ent114 = Script_114 [Att10]  [Ent99]  | Noscript_114 [Att11]  [Ent98]  | Div_114 [Att11]  [Ent100]  | P_114 [Att11]  [Ent113]  | H1_114 [Att11]  [Ent113]  | H2_114 [Att11]  [Ent113]  | H3_114 [Att11]  [Ent113]  | H4_114 [Att11]  [Ent113]  | H5_114 [Att11]  [Ent113]  | H6_114 [Att11]  [Ent113]  | Ul_114 [Att11]  [Ent125]  | Ol_114 [Att11]  [Ent125]  | Dl_114 [Att11]  [Ent126]  | Address_114 [Att11]  [Ent113]  | Hr_114 [Att11]  | Pre_114 [Att11]  [Ent127]  | Blockquote_114 [Att13]  [Ent98]  | Ins_114 [Att14]  [Ent100]  | Del_114 [Att14]  [Ent100]  | A_114 [Att15]  [Ent13]  | Span_114 [Att11]  [Ent113]  | Bdo_114 [Att11]  [Ent113]  | Br_114 [Att18]  | Em_114 [Att11]  [Ent113]  | Strong_114 [Att11]  [Ent113]  | Dfn_114 [Att11]  [Ent113]  | Code_114 [Att11]  [Ent113]  | Samp_114 [Att11]  [Ent113]  | Kbd_114 [Att11]  [Ent113]  | Var_114 [Att11]  [Ent113]  | Cite_114 [Att11]  [Ent113]  | Abbr_114 [Att11]  [Ent113]  | Acronym_114 [Att11]  [Ent113]  | Q_114 [Att13]  [Ent113]  | Sub_114 [Att11]  [Ent113]  | Sup_114 [Att11]  [Ent113]  | Tt_114 [Att11]  [Ent113]  | I_114 [Att11]  [Ent113]  | B_114 [Att11]  [Ent113]  | Big_114 [Att11]  [Ent113]  | Small_114 [Att11]  [Ent113]  | Object_114 [Att19]  [Ent114]  | Param_114 [Att20]  | Img_114 [Att21]  | Map_114 [Att24]  [Ent115]  | Label_114 [Att29]  [Ent71]  | Input_114 [Att30]  | Select_114 [Att31]  [Ent122]  | Textarea_114 [Att35]  [Ent99]  | Fieldset_114 [Att11]  [Ent128]  | Button_114 [Att39]  [Ent124]  | Table_114 [Att40]  [Ent129]  | PCDATA_114 [Att0] B.ByteString
    deriving (Show)

data Ent115 = Script_115 [Att10]  [Ent99]  | Noscript_115 [Att11]  [Ent98]  | Div_115 [Att11]  [Ent100]  | P_115 [Att11]  [Ent113]  | H1_115 [Att11]  [Ent113]  | H2_115 [Att11]  [Ent113]  | H3_115 [Att11]  [Ent113]  | H4_115 [Att11]  [Ent113]  | H5_115 [Att11]  [Ent113]  | H6_115 [Att11]  [Ent113]  | Ul_115 [Att11]  [Ent125]  | Ol_115 [Att11]  [Ent125]  | Dl_115 [Att11]  [Ent126]  | Address_115 [Att11]  [Ent113]  | Hr_115 [Att11]  | Pre_115 [Att11]  [Ent127]  | Blockquote_115 [Att13]  [Ent98]  | Ins_115 [Att14]  [Ent100]  | Del_115 [Att14]  [Ent100]  | Area_115 [Att26]  | Fieldset_115 [Att11]  [Ent128]  | Table_115 [Att40]  [Ent129] 
    deriving (Show)

data Ent116 = PCDATA_116 [Att0] B.ByteString
    deriving (Show)

data Ent117 = Script_117 [Att10]  [Ent116]  | Noscript_117 [Att11]  [Ent69]  | Div_117 [Att11]  [Ent70]  | P_117 [Att11]  [Ent71]  | H1_117 [Att11]  [Ent71]  | H2_117 [Att11]  [Ent71]  | H3_117 [Att11]  [Ent71]  | H4_117 [Att11]  [Ent71]  | H5_117 [Att11]  [Ent71]  | H6_117 [Att11]  [Ent71]  | Ul_117 [Att11]  [Ent72]  | Ol_117 [Att11]  [Ent72]  | Dl_117 [Att11]  [Ent73]  | Address_117 [Att11]  [Ent71]  | Hr_117 [Att11]  | Pre_117 [Att11]  [Ent74]  | Blockquote_117 [Att13]  [Ent69]  | Ins_117 [Att14]  [Ent70]  | Del_117 [Att14]  [Ent70]  | A_117 [Att15]  [Ent38]  | Span_117 [Att11]  [Ent71]  | Bdo_117 [Att11]  [Ent71]  | Br_117 [Att18]  | Em_117 [Att11]  [Ent71]  | Strong_117 [Att11]  [Ent71]  | Dfn_117 [Att11]  [Ent71]  | Code_117 [Att11]  [Ent71]  | Samp_117 [Att11]  [Ent71]  | Kbd_117 [Att11]  [Ent71]  | Var_117 [Att11]  [Ent71]  | Cite_117 [Att11]  [Ent71]  | Abbr_117 [Att11]  [Ent71]  | Acronym_117 [Att11]  [Ent71]  | Q_117 [Att13]  [Ent71]  | Sub_117 [Att11]  [Ent71]  | Sup_117 [Att11]  [Ent71]  | Tt_117 [Att11]  [Ent71]  | I_117 [Att11]  [Ent71]  | B_117 [Att11]  [Ent71]  | Big_117 [Att11]  [Ent71]  | Small_117 [Att11]  [Ent71]  | Object_117 [Att19]  [Ent117]  | Param_117 [Att20]  | Img_117 [Att21]  | Map_117 [Att24]  [Ent118]  | Input_117 [Att30]  | Select_117 [Att31]  [Ent119]  | Textarea_117 [Att35]  [Ent116]  | Fieldset_117 [Att11]  [Ent75]  | Button_117 [Att39]  [Ent121]  | Table_117 [Att40]  [Ent76]  | PCDATA_117 [Att0] B.ByteString
    deriving (Show)

data Ent118 = Script_118 [Att10]  [Ent116]  | Noscript_118 [Att11]  [Ent69]  | Div_118 [Att11]  [Ent70]  | P_118 [Att11]  [Ent71]  | H1_118 [Att11]  [Ent71]  | H2_118 [Att11]  [Ent71]  | H3_118 [Att11]  [Ent71]  | H4_118 [Att11]  [Ent71]  | H5_118 [Att11]  [Ent71]  | H6_118 [Att11]  [Ent71]  | Ul_118 [Att11]  [Ent72]  | Ol_118 [Att11]  [Ent72]  | Dl_118 [Att11]  [Ent73]  | Address_118 [Att11]  [Ent71]  | Hr_118 [Att11]  | Pre_118 [Att11]  [Ent74]  | Blockquote_118 [Att13]  [Ent69]  | Ins_118 [Att14]  [Ent70]  | Del_118 [Att14]  [Ent70]  | Area_118 [Att26]  | Fieldset_118 [Att11]  [Ent75]  | Table_118 [Att40]  [Ent76] 
    deriving (Show)

data Ent119 = Optgroup_119 [Att32]  [Ent120]  | Option_119 [Att34]  [Ent116] 
    deriving (Show)

data Ent120 = Option_120 [Att34]  [Ent116] 
    deriving (Show)

data Ent121 = Script_121 [Att10]  [Ent116]  | Noscript_121 [Att11]  [Ent69]  | Div_121 [Att11]  [Ent70]  | P_121 [Att11]  [Ent71]  | H1_121 [Att11]  [Ent71]  | H2_121 [Att11]  [Ent71]  | H3_121 [Att11]  [Ent71]  | H4_121 [Att11]  [Ent71]  | H5_121 [Att11]  [Ent71]  | H6_121 [Att11]  [Ent71]  | Ul_121 [Att11]  [Ent72]  | Ol_121 [Att11]  [Ent72]  | Dl_121 [Att11]  [Ent73]  | Address_121 [Att11]  [Ent71]  | Hr_121 [Att11]  | Pre_121 [Att11]  [Ent74]  | Blockquote_121 [Att13]  [Ent69]  | Ins_121 [Att14]  [Ent70]  | Del_121 [Att14]  [Ent70]  | Span_121 [Att11]  [Ent71]  | Bdo_121 [Att11]  [Ent71]  | Br_121 [Att18]  | Em_121 [Att11]  [Ent71]  | Strong_121 [Att11]  [Ent71]  | Dfn_121 [Att11]  [Ent71]  | Code_121 [Att11]  [Ent71]  | Samp_121 [Att11]  [Ent71]  | Kbd_121 [Att11]  [Ent71]  | Var_121 [Att11]  [Ent71]  | Cite_121 [Att11]  [Ent71]  | Abbr_121 [Att11]  [Ent71]  | Acronym_121 [Att11]  [Ent71]  | Q_121 [Att13]  [Ent71]  | Sub_121 [Att11]  [Ent71]  | Sup_121 [Att11]  [Ent71]  | Tt_121 [Att11]  [Ent71]  | I_121 [Att11]  [Ent71]  | B_121 [Att11]  [Ent71]  | Big_121 [Att11]  [Ent71]  | Small_121 [Att11]  [Ent71]  | Object_121 [Att19]  [Ent117]  | Img_121 [Att21]  | Map_121 [Att24]  [Ent118]  | Table_121 [Att40]  [Ent76]  | PCDATA_121 [Att0] B.ByteString
    deriving (Show)

data Ent122 = Optgroup_122 [Att32]  [Ent123]  | Option_122 [Att34]  [Ent99] 
    deriving (Show)

data Ent123 = Option_123 [Att34]  [Ent99] 
    deriving (Show)

data Ent124 = Script_124 [Att10]  [Ent99]  | Noscript_124 [Att11]  [Ent98]  | Div_124 [Att11]  [Ent100]  | P_124 [Att11]  [Ent113]  | H1_124 [Att11]  [Ent113]  | H2_124 [Att11]  [Ent113]  | H3_124 [Att11]  [Ent113]  | H4_124 [Att11]  [Ent113]  | H5_124 [Att11]  [Ent113]  | H6_124 [Att11]  [Ent113]  | Ul_124 [Att11]  [Ent125]  | Ol_124 [Att11]  [Ent125]  | Dl_124 [Att11]  [Ent126]  | Address_124 [Att11]  [Ent113]  | Hr_124 [Att11]  | Pre_124 [Att11]  [Ent127]  | Blockquote_124 [Att13]  [Ent98]  | Ins_124 [Att14]  [Ent100]  | Del_124 [Att14]  [Ent100]  | Span_124 [Att11]  [Ent113]  | Bdo_124 [Att11]  [Ent113]  | Br_124 [Att18]  | Em_124 [Att11]  [Ent113]  | Strong_124 [Att11]  [Ent113]  | Dfn_124 [Att11]  [Ent113]  | Code_124 [Att11]  [Ent113]  | Samp_124 [Att11]  [Ent113]  | Kbd_124 [Att11]  [Ent113]  | Var_124 [Att11]  [Ent113]  | Cite_124 [Att11]  [Ent113]  | Abbr_124 [Att11]  [Ent113]  | Acronym_124 [Att11]  [Ent113]  | Q_124 [Att13]  [Ent113]  | Sub_124 [Att11]  [Ent113]  | Sup_124 [Att11]  [Ent113]  | Tt_124 [Att11]  [Ent113]  | I_124 [Att11]  [Ent113]  | B_124 [Att11]  [Ent113]  | Big_124 [Att11]  [Ent113]  | Small_124 [Att11]  [Ent113]  | Object_124 [Att19]  [Ent114]  | Img_124 [Att21]  | Map_124 [Att24]  [Ent115]  | Table_124 [Att40]  [Ent129]  | PCDATA_124 [Att0] B.ByteString
    deriving (Show)

data Ent125 = Li_125 [Att11]  [Ent100] 
    deriving (Show)

data Ent126 = Dt_126 [Att11]  [Ent113]  | Dd_126 [Att11]  [Ent100] 
    deriving (Show)

data Ent127 = Script_127 [Att10]  [Ent99]  | Ins_127 [Att14]  [Ent100]  | Del_127 [Att14]  [Ent100]  | A_127 [Att15]  [Ent13]  | Span_127 [Att11]  [Ent113]  | Bdo_127 [Att11]  [Ent113]  | Br_127 [Att18]  | Em_127 [Att11]  [Ent113]  | Strong_127 [Att11]  [Ent113]  | Dfn_127 [Att11]  [Ent113]  | Code_127 [Att11]  [Ent113]  | Samp_127 [Att11]  [Ent113]  | Kbd_127 [Att11]  [Ent113]  | Var_127 [Att11]  [Ent113]  | Cite_127 [Att11]  [Ent113]  | Abbr_127 [Att11]  [Ent113]  | Acronym_127 [Att11]  [Ent113]  | Q_127 [Att13]  [Ent113]  | Sub_127 [Att11]  [Ent113]  | Sup_127 [Att11]  [Ent113]  | Tt_127 [Att11]  [Ent113]  | I_127 [Att11]  [Ent113]  | B_127 [Att11]  [Ent113]  | Big_127 [Att11]  [Ent113]  | Small_127 [Att11]  [Ent113]  | Map_127 [Att24]  [Ent115]  | Label_127 [Att29]  [Ent71]  | Input_127 [Att30]  | Select_127 [Att31]  [Ent122]  | Textarea_127 [Att35]  [Ent99]  | Button_127 [Att39]  [Ent124]  | PCDATA_127 [Att0] B.ByteString
    deriving (Show)

data Ent128 = Script_128 [Att10]  [Ent99]  | Noscript_128 [Att11]  [Ent98]  | Div_128 [Att11]  [Ent100]  | P_128 [Att11]  [Ent113]  | H1_128 [Att11]  [Ent113]  | H2_128 [Att11]  [Ent113]  | H3_128 [Att11]  [Ent113]  | H4_128 [Att11]  [Ent113]  | H5_128 [Att11]  [Ent113]  | H6_128 [Att11]  [Ent113]  | Ul_128 [Att11]  [Ent125]  | Ol_128 [Att11]  [Ent125]  | Dl_128 [Att11]  [Ent126]  | Address_128 [Att11]  [Ent113]  | Hr_128 [Att11]  | Pre_128 [Att11]  [Ent127]  | Blockquote_128 [Att13]  [Ent98]  | Ins_128 [Att14]  [Ent100]  | Del_128 [Att14]  [Ent100]  | A_128 [Att15]  [Ent13]  | Span_128 [Att11]  [Ent113]  | Bdo_128 [Att11]  [Ent113]  | Br_128 [Att18]  | Em_128 [Att11]  [Ent113]  | Strong_128 [Att11]  [Ent113]  | Dfn_128 [Att11]  [Ent113]  | Code_128 [Att11]  [Ent113]  | Samp_128 [Att11]  [Ent113]  | Kbd_128 [Att11]  [Ent113]  | Var_128 [Att11]  [Ent113]  | Cite_128 [Att11]  [Ent113]  | Abbr_128 [Att11]  [Ent113]  | Acronym_128 [Att11]  [Ent113]  | Q_128 [Att13]  [Ent113]  | Sub_128 [Att11]  [Ent113]  | Sup_128 [Att11]  [Ent113]  | Tt_128 [Att11]  [Ent113]  | I_128 [Att11]  [Ent113]  | B_128 [Att11]  [Ent113]  | Big_128 [Att11]  [Ent113]  | Small_128 [Att11]  [Ent113]  | Object_128 [Att19]  [Ent114]  | Img_128 [Att21]  | Map_128 [Att24]  [Ent115]  | Label_128 [Att29]  [Ent71]  | Input_128 [Att30]  | Select_128 [Att31]  [Ent122]  | Textarea_128 [Att35]  [Ent99]  | Fieldset_128 [Att11]  [Ent128]  | Legend_128 [Att38]  [Ent113]  | Button_128 [Att39]  [Ent124]  | Table_128 [Att40]  [Ent129]  | PCDATA_128 [Att0] B.ByteString
    deriving (Show)

data Ent129 = Caption_129 [Att11]  [Ent113]  | Thead_129 [Att41]  [Ent130]  | Tfoot_129 [Att41]  [Ent130]  | Tbody_129 [Att41]  [Ent130]  | Colgroup_129 [Att42]  [Ent131]  | Col_129 [Att42]  | Tr_129 [Att41]  [Ent132] 
    deriving (Show)

data Ent130 = Tr_130 [Att41]  [Ent132] 
    deriving (Show)

data Ent131 = Col_131 [Att42] 
    deriving (Show)

data Ent132 = Th_132 [Att43]  [Ent100]  | Td_132 [Att43]  [Ent100] 
    deriving (Show)

data Ent133 = Script_133 [Att10]  [Ent2]  | Noscript_133 [Att11]  [Ent93]  | Div_133 [Att11]  [Ent94]  | P_133 [Att11]  [Ent60]  | H1_133 [Att11]  [Ent60]  | H2_133 [Att11]  [Ent60]  | H3_133 [Att11]  [Ent60]  | H4_133 [Att11]  [Ent60]  | H5_133 [Att11]  [Ent60]  | H6_133 [Att11]  [Ent60]  | Ul_133 [Att11]  [Ent95]  | Ol_133 [Att11]  [Ent95]  | Dl_133 [Att11]  [Ent96]  | Address_133 [Att11]  [Ent60]  | Hr_133 [Att11]  | Pre_133 [Att11]  [Ent97]  | Blockquote_133 [Att13]  [Ent93]  | Ins_133 [Att14]  [Ent94]  | Del_133 [Att14]  [Ent94]  | A_133 [Att15]  [Ent4]  | Span_133 [Att11]  [Ent60]  | Bdo_133 [Att11]  [Ent60]  | Br_133 [Att18]  | Em_133 [Att11]  [Ent60]  | Strong_133 [Att11]  [Ent60]  | Dfn_133 [Att11]  [Ent60]  | Code_133 [Att11]  [Ent60]  | Samp_133 [Att11]  [Ent60]  | Kbd_133 [Att11]  [Ent60]  | Var_133 [Att11]  [Ent60]  | Cite_133 [Att11]  [Ent60]  | Abbr_133 [Att11]  [Ent60]  | Acronym_133 [Att11]  [Ent60]  | Q_133 [Att13]  [Ent60]  | Sub_133 [Att11]  [Ent60]  | Sup_133 [Att11]  [Ent60]  | Tt_133 [Att11]  [Ent60]  | I_133 [Att11]  [Ent60]  | B_133 [Att11]  [Ent60]  | Big_133 [Att11]  [Ent60]  | Small_133 [Att11]  [Ent60]  | Object_133 [Att19]  [Ent3]  | Img_133 [Att21]  | Map_133 [Att24]  [Ent61]  | Form_133 [Att27]  [Ent98]  | Label_133 [Att29]  [Ent62]  | Input_133 [Att30]  | Select_133 [Att31]  [Ent90]  | Textarea_133 [Att35]  [Ent2]  | Fieldset_133 [Att11]  [Ent133]  | Legend_133 [Att38]  [Ent60]  | Button_133 [Att39]  [Ent92]  | Table_133 [Att40]  [Ent134]  | PCDATA_133 [Att0] B.ByteString
    deriving (Show)

data Ent134 = Caption_134 [Att11]  [Ent60]  | Thead_134 [Att41]  [Ent135]  | Tfoot_134 [Att41]  [Ent135]  | Tbody_134 [Att41]  [Ent135]  | Colgroup_134 [Att42]  [Ent136]  | Col_134 [Att42]  | Tr_134 [Att41]  [Ent137] 
    deriving (Show)

data Ent135 = Tr_135 [Att41]  [Ent137] 
    deriving (Show)

data Ent136 = Col_136 [Att42] 
    deriving (Show)

data Ent137 = Th_137 [Att43]  [Ent94]  | Td_137 [Att43]  [Ent94] 
    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 = Head_0 []
    head_  = Head_0 

class C_Title a b | a -> b where
    _title :: [b] -> a
    title_ :: [Att2] -> [b] -> a
instance C_Title Ent1 Ent2 where
    _title = Title_1 []
    title_  = Title_1 

class C_Base a where
    _base :: a
    base_ :: [Att3] -> a
instance C_Base Ent1 where
    _base = Base_1 []
    base_ = Base_1 

class C_Meta a where
    _meta :: a
    meta_ :: [Att5] -> a
instance C_Meta Ent1 where
    _meta = Meta_1 []
    meta_ = Meta_1 

class C_Link a where
    _link :: a
    link_ :: [Att7] -> a
instance C_Link Ent1 where
    _link = Link_1 []
    link_ = Link_1 

class C_Style a b | a -> b where
    _style :: [b] -> a
    style_ :: [Att8] -> [b] -> a
instance C_Style Ent1 Ent2 where
    _style = Style_1 []
    style_  = Style_1 

class C_Script a b | a -> b where
    _script :: [b] -> a
    script_ :: [Att10] -> [b] -> a
instance C_Script Ent1 Ent2 where
    _script = Script_1 []
    script_  = Script_1 
instance C_Script Ent3 Ent2 where
    _script = Script_3 []
    script_  = Script_3 
instance C_Script Ent4 Ent5 where
    _script = Script_4 []
    script_  = Script_4 
instance C_Script Ent6 Ent5 where
    _script = Script_6 []
    script_  = Script_6 
instance C_Script Ent7 Ent5 where
    _script = Script_7 []
    script_  = Script_7 
instance C_Script Ent10 Ent5 where
    _script = Script_10 []
    script_  = Script_10 
instance C_Script Ent11 Ent101 where
    _script = Script_11 []
    script_  = Script_11 
instance C_Script Ent12 Ent101 where
    _script = Script_12 []
    script_  = Script_12 
instance C_Script Ent13 Ent101 where
    _script = Script_13 []
    script_  = Script_13 
instance C_Script Ent16 Ent101 where
    _script = Script_16 []
    script_  = Script_16 
instance C_Script Ent17 Ent101 where
    _script = Script_17 []
    script_  = Script_17 
instance C_Script Ent22 Ent5 where
    _script = Script_22 []
    script_  = Script_22 
instance C_Script Ent27 Ent5 where
    _script = Script_27 []
    script_  = Script_27 
instance C_Script Ent28 Ent5 where
    _script = Script_28 []
    script_  = Script_28 
instance C_Script Ent29 Ent30 where
    _script = Script_29 []
    script_  = Script_29 
instance C_Script Ent31 Ent30 where
    _script = Script_31 []
    script_  = Script_31 
instance C_Script Ent32 Ent30 where
    _script = Script_32 []
    script_  = Script_32 
instance C_Script Ent35 Ent30 where
    _script = Script_35 []
    script_  = Script_35 
instance C_Script Ent36 Ent104 where
    _script = Script_36 []
    script_  = Script_36 
instance C_Script Ent37 Ent104 where
    _script = Script_37 []
    script_  = Script_37 
instance C_Script Ent38 Ent104 where
    _script = Script_38 []
    script_  = Script_38 
instance C_Script Ent41 Ent104 where
    _script = Script_41 []
    script_  = Script_41 
instance C_Script Ent42 Ent104 where
    _script = Script_42 []
    script_  = Script_42 
instance C_Script Ent47 Ent30 where
    _script = Script_47 []
    script_  = Script_47 
instance C_Script Ent52 Ent30 where
    _script = Script_52 []
    script_  = Script_52 
instance C_Script Ent53 Ent30 where
    _script = Script_53 []
    script_  = Script_53 
instance C_Script Ent56 Ent30 where
    _script = Script_56 []
    script_  = Script_56 
instance C_Script Ent59 Ent5 where
    _script = Script_59 []
    script_  = Script_59 
instance C_Script Ent60 Ent2 where
    _script = Script_60 []
    script_  = Script_60 
instance C_Script Ent61 Ent2 where
    _script = Script_61 []
    script_  = Script_61 
instance C_Script Ent62 Ent63 where
    _script = Script_62 []
    script_  = Script_62 
instance C_Script Ent64 Ent63 where
    _script = Script_64 []
    script_  = Script_64 
instance C_Script Ent65 Ent63 where
    _script = Script_65 []
    script_  = Script_65 
instance C_Script Ent68 Ent63 where
    _script = Script_68 []
    script_  = Script_68 
instance C_Script Ent69 Ent116 where
    _script = Script_69 []
    script_  = Script_69 
instance C_Script Ent70 Ent116 where
    _script = Script_70 []
    script_  = Script_70 
instance C_Script Ent71 Ent116 where
    _script = Script_71 []
    script_  = Script_71 
instance C_Script Ent74 Ent116 where
    _script = Script_74 []
    script_  = Script_74 
instance C_Script Ent75 Ent116 where
    _script = Script_75 []
    script_  = Script_75 
instance C_Script Ent80 Ent63 where
    _script = Script_80 []
    script_  = Script_80 
instance C_Script Ent85 Ent63 where
    _script = Script_85 []
    script_  = Script_85 
instance C_Script Ent86 Ent63 where
    _script = Script_86 []
    script_  = Script_86 
instance C_Script Ent89 Ent63 where
    _script = Script_89 []
    script_  = Script_89 
instance C_Script Ent92 Ent2 where
    _script = Script_92 []
    script_  = Script_92 
instance C_Script Ent93 Ent2 where
    _script = Script_93 []
    script_  = Script_93 
instance C_Script Ent94 Ent2 where
    _script = Script_94 []
    script_  = Script_94 
instance C_Script Ent97 Ent2 where
    _script = Script_97 []
    script_  = Script_97 
instance C_Script Ent98 Ent99 where
    _script = Script_98 []
    script_  = Script_98 
instance C_Script Ent100 Ent99 where
    _script = Script_100 []
    script_  = Script_100 
instance C_Script Ent102 Ent101 where
    _script = Script_102 []
    script_  = Script_102 
instance C_Script Ent103 Ent101 where
    _script = Script_103 []
    script_  = Script_103 
instance C_Script Ent105 Ent104 where
    _script = Script_105 []
    script_  = Script_105 
instance C_Script Ent106 Ent104 where
    _script = Script_106 []
    script_  = Script_106 
instance C_Script Ent109 Ent104 where
    _script = Script_109 []
    script_  = Script_109 
instance C_Script Ent112 Ent101 where
    _script = Script_112 []
    script_  = Script_112 
instance C_Script Ent113 Ent99 where
    _script = Script_113 []
    script_  = Script_113 
instance C_Script Ent114 Ent99 where
    _script = Script_114 []
    script_  = Script_114 
instance C_Script Ent115 Ent99 where
    _script = Script_115 []
    script_  = Script_115 
instance C_Script Ent117 Ent116 where
    _script = Script_117 []
    script_  = Script_117 
instance C_Script Ent118 Ent116 where
    _script = Script_118 []
    script_  = Script_118 
instance C_Script Ent121 Ent116 where
    _script = Script_121 []
    script_  = Script_121 
instance C_Script Ent124 Ent99 where
    _script = Script_124 []
    script_  = Script_124 
instance C_Script Ent127 Ent99 where
    _script = Script_127 []
    script_  = Script_127 
instance C_Script Ent128 Ent99 where
    _script = Script_128 []
    script_  = Script_128 
instance C_Script Ent133 Ent2 where
    _script = Script_133 []
    script_  = Script_133 

class C_Noscript a b | a -> b where
    _noscript :: [b] -> a
    noscript_ :: [Att11] -> [b] -> a
instance C_Noscript Ent3 Ent93 where
    _noscript = Noscript_3 []
    noscript_  = Noscript_3 
instance C_Noscript Ent6 Ent7 where
    _noscript = Noscript_6 []
    noscript_  = Noscript_6 
instance C_Noscript Ent7 Ent7 where
    _noscript = Noscript_7 []
    noscript_  = Noscript_7 
instance C_Noscript Ent11 Ent11 where
    _noscript = Noscript_11 []
    noscript_  = Noscript_11 
instance C_Noscript Ent12 Ent11 where
    _noscript = Noscript_12 []
    noscript_  = Noscript_12 
instance C_Noscript Ent17 Ent11 where
    _noscript = Noscript_17 []
    noscript_  = Noscript_17 
instance C_Noscript Ent22 Ent7 where
    _noscript = Noscript_22 []
    noscript_  = Noscript_22 
instance C_Noscript Ent27 Ent7 where
    _noscript = Noscript_27 []
    noscript_  = Noscript_27 
instance C_Noscript Ent28 Ent7 where
    _noscript = Noscript_28 []
    noscript_  = Noscript_28 
instance C_Noscript Ent31 Ent32 where
    _noscript = Noscript_31 []
    noscript_  = Noscript_31 
instance C_Noscript Ent32 Ent32 where
    _noscript = Noscript_32 []
    noscript_  = Noscript_32 
instance C_Noscript Ent36 Ent36 where
    _noscript = Noscript_36 []
    noscript_  = Noscript_36 
instance C_Noscript Ent37 Ent36 where
    _noscript = Noscript_37 []
    noscript_  = Noscript_37 
instance C_Noscript Ent42 Ent36 where
    _noscript = Noscript_42 []
    noscript_  = Noscript_42 
instance C_Noscript Ent47 Ent32 where
    _noscript = Noscript_47 []
    noscript_  = Noscript_47 
instance C_Noscript Ent52 Ent32 where
    _noscript = Noscript_52 []
    noscript_  = Noscript_52 
instance C_Noscript Ent53 Ent32 where
    _noscript = Noscript_53 []
    noscript_  = Noscript_53 
instance C_Noscript Ent56 Ent32 where
    _noscript = Noscript_56 []
    noscript_  = Noscript_56 
instance C_Noscript Ent59 Ent7 where
    _noscript = Noscript_59 []
    noscript_  = Noscript_59 
instance C_Noscript Ent61 Ent93 where
    _noscript = Noscript_61 []
    noscript_  = Noscript_61 
instance C_Noscript Ent64 Ent65 where
    _noscript = Noscript_64 []
    noscript_  = Noscript_64 
instance C_Noscript Ent65 Ent65 where
    _noscript = Noscript_65 []
    noscript_  = Noscript_65 
instance C_Noscript Ent69 Ent69 where
    _noscript = Noscript_69 []
    noscript_  = Noscript_69 
instance C_Noscript Ent70 Ent69 where
    _noscript = Noscript_70 []
    noscript_  = Noscript_70 
instance C_Noscript Ent75 Ent69 where
    _noscript = Noscript_75 []
    noscript_  = Noscript_75 
instance C_Noscript Ent80 Ent65 where
    _noscript = Noscript_80 []
    noscript_  = Noscript_80 
instance C_Noscript Ent85 Ent65 where
    _noscript = Noscript_85 []
    noscript_  = Noscript_85 
instance C_Noscript Ent86 Ent65 where
    _noscript = Noscript_86 []
    noscript_  = Noscript_86 
instance C_Noscript Ent89 Ent65 where
    _noscript = Noscript_89 []
    noscript_  = Noscript_89 
instance C_Noscript Ent92 Ent93 where
    _noscript = Noscript_92 []
    noscript_  = Noscript_92 
instance C_Noscript Ent93 Ent93 where
    _noscript = Noscript_93 []
    noscript_  = Noscript_93 
instance C_Noscript Ent94 Ent93 where
    _noscript = Noscript_94 []
    noscript_  = Noscript_94 
instance C_Noscript Ent98 Ent98 where
    _noscript = Noscript_98 []
    noscript_  = Noscript_98 
instance C_Noscript Ent100 Ent98 where
    _noscript = Noscript_100 []
    noscript_  = Noscript_100 
instance C_Noscript Ent102 Ent11 where
    _noscript = Noscript_102 []
    noscript_  = Noscript_102 
instance C_Noscript Ent103 Ent11 where
    _noscript = Noscript_103 []
    noscript_  = Noscript_103 
instance C_Noscript Ent105 Ent36 where
    _noscript = Noscript_105 []
    noscript_  = Noscript_105 
instance C_Noscript Ent106 Ent36 where
    _noscript = Noscript_106 []
    noscript_  = Noscript_106 
instance C_Noscript Ent109 Ent36 where
    _noscript = Noscript_109 []
    noscript_  = Noscript_109 
instance C_Noscript Ent112 Ent11 where
    _noscript = Noscript_112 []
    noscript_  = Noscript_112 
instance C_Noscript Ent114 Ent98 where
    _noscript = Noscript_114 []
    noscript_  = Noscript_114 
instance C_Noscript Ent115 Ent98 where
    _noscript = Noscript_115 []
    noscript_  = Noscript_115 
instance C_Noscript Ent117 Ent69 where
    _noscript = Noscript_117 []
    noscript_  = Noscript_117 
instance C_Noscript Ent118 Ent69 where
    _noscript = Noscript_118 []
    noscript_  = Noscript_118 
instance C_Noscript Ent121 Ent69 where
    _noscript = Noscript_121 []
    noscript_  = Noscript_121 
instance C_Noscript Ent124 Ent98 where
    _noscript = Noscript_124 []
    noscript_  = Noscript_124 
instance C_Noscript Ent128 Ent98 where
    _noscript = Noscript_128 []
    noscript_  = Noscript_128 
instance C_Noscript Ent133 Ent93 where
    _noscript = Noscript_133 []
    noscript_  = Noscript_133 

class C_Body a b | a -> b where
    _body :: [b] -> a
    body_ :: [Att12] -> [b] -> a
instance C_Body Ent0 Ent93 where
    _body = Body_0 []
    body_  = Body_0 

class C_Div a b | a -> b where
    _div :: [b] -> a
    div_ :: [Att11] -> [b] -> a
instance C_Div Ent3 Ent94 where
    _div = Div_3 []
    div_  = Div_3 
instance C_Div Ent6 Ent6 where
    _div = Div_6 []
    div_  = Div_6 
instance C_Div Ent7 Ent6 where
    _div = Div_7 []
    div_  = Div_7 
instance C_Div Ent11 Ent12 where
    _div = Div_11 []
    div_  = Div_11 
instance C_Div Ent12 Ent12 where
    _div = Div_12 []
    div_  = Div_12 
instance C_Div Ent17 Ent12 where
    _div = Div_17 []
    div_  = Div_17 
instance C_Div Ent22 Ent6 where
    _div = Div_22 []
    div_  = Div_22 
instance C_Div Ent27 Ent6 where
    _div = Div_27 []
    div_  = Div_27 
instance C_Div Ent28 Ent6 where
    _div = Div_28 []
    div_  = Div_28 
instance C_Div Ent31 Ent31 where
    _div = Div_31 []
    div_  = Div_31 
instance C_Div Ent32 Ent31 where
    _div = Div_32 []
    div_  = Div_32 
instance C_Div Ent36 Ent37 where
    _div = Div_36 []
    div_  = Div_36 
instance C_Div Ent37 Ent37 where
    _div = Div_37 []
    div_  = Div_37 
instance C_Div Ent42 Ent37 where
    _div = Div_42 []
    div_  = Div_42 
instance C_Div Ent47 Ent31 where
    _div = Div_47 []
    div_  = Div_47 
instance C_Div Ent52 Ent31 where
    _div = Div_52 []
    div_  = Div_52 
instance C_Div Ent53 Ent31 where
    _div = Div_53 []
    div_  = Div_53 
instance C_Div Ent56 Ent31 where
    _div = Div_56 []
    div_  = Div_56 
instance C_Div Ent59 Ent6 where
    _div = Div_59 []
    div_  = Div_59 
instance C_Div Ent61 Ent94 where
    _div = Div_61 []
    div_  = Div_61 
instance C_Div Ent64 Ent64 where
    _div = Div_64 []
    div_  = Div_64 
instance C_Div Ent65 Ent64 where
    _div = Div_65 []
    div_  = Div_65 
instance C_Div Ent69 Ent70 where
    _div = Div_69 []
    div_  = Div_69 
instance C_Div Ent70 Ent70 where
    _div = Div_70 []
    div_  = Div_70 
instance C_Div Ent75 Ent70 where
    _div = Div_75 []
    div_  = Div_75 
instance C_Div Ent80 Ent64 where
    _div = Div_80 []
    div_  = Div_80 
instance C_Div Ent85 Ent64 where
    _div = Div_85 []
    div_  = Div_85 
instance C_Div Ent86 Ent64 where
    _div = Div_86 []
    div_  = Div_86 
instance C_Div Ent89 Ent64 where
    _div = Div_89 []
    div_  = Div_89 
instance C_Div Ent92 Ent94 where
    _div = Div_92 []
    div_  = Div_92 
instance C_Div Ent93 Ent94 where
    _div = Div_93 []
    div_  = Div_93 
instance C_Div Ent94 Ent94 where
    _div = Div_94 []
    div_  = Div_94 
instance C_Div Ent98 Ent100 where
    _div = Div_98 []
    div_  = Div_98 
instance C_Div Ent100 Ent100 where
    _div = Div_100 []
    div_  = Div_100 
instance C_Div Ent102 Ent12 where
    _div = Div_102 []
    div_  = Div_102 
instance C_Div Ent103 Ent12 where
    _div = Div_103 []
    div_  = Div_103 
instance C_Div Ent105 Ent37 where
    _div = Div_105 []
    div_  = Div_105 
instance C_Div Ent106 Ent37 where
    _div = Div_106 []
    div_  = Div_106 
instance C_Div Ent109 Ent37 where
    _div = Div_109 []
    div_  = Div_109 
instance C_Div Ent112 Ent12 where
    _div = Div_112 []
    div_  = Div_112 
instance C_Div Ent114 Ent100 where
    _div = Div_114 []
    div_  = Div_114 
instance C_Div Ent115 Ent100 where
    _div = Div_115 []
    div_  = Div_115 
instance C_Div Ent117 Ent70 where
    _div = Div_117 []
    div_  = Div_117 
instance C_Div Ent118 Ent70 where
    _div = Div_118 []
    div_  = Div_118 
instance C_Div Ent121 Ent70 where
    _div = Div_121 []
    div_  = Div_121 
instance C_Div Ent124 Ent100 where
    _div = Div_124 []
    div_  = Div_124 
instance C_Div Ent128 Ent100 where
    _div = Div_128 []
    div_  = Div_128 
instance C_Div Ent133 Ent94 where
    _div = Div_133 []
    div_  = Div_133 

class C_P a b | a -> b where
    _p :: [b] -> a
    p_ :: [Att11] -> [b] -> a
instance C_P Ent3 Ent60 where
    _p = P_3 []
    p_  = P_3 
instance C_P Ent6 Ent4 where
    _p = P_6 []
    p_  = P_6 
instance C_P Ent7 Ent4 where
    _p = P_7 []
    p_  = P_7 
instance C_P Ent11 Ent13 where
    _p = P_11 []
    p_  = P_11 
instance C_P Ent12 Ent13 where
    _p = P_12 []
    p_  = P_12 
instance C_P Ent17 Ent13 where
    _p = P_17 []
    p_  = P_17 
instance C_P Ent22 Ent4 where
    _p = P_22 []
    p_  = P_22 
instance C_P Ent27 Ent4 where
    _p = P_27 []
    p_  = P_27 
instance C_P Ent28 Ent4 where
    _p = P_28 []
    p_  = P_28 
instance C_P Ent31 Ent29 where
    _p = P_31 []
    p_  = P_31 
instance C_P Ent32 Ent29 where
    _p = P_32 []
    p_  = P_32 
instance C_P Ent36 Ent38 where
    _p = P_36 []
    p_  = P_36 
instance C_P Ent37 Ent38 where
    _p = P_37 []
    p_  = P_37 
instance C_P Ent42 Ent38 where
    _p = P_42 []
    p_  = P_42 
instance C_P Ent47 Ent29 where
    _p = P_47 []
    p_  = P_47 
instance C_P Ent52 Ent29 where
    _p = P_52 []
    p_  = P_52 
instance C_P Ent53 Ent29 where
    _p = P_53 []
    p_  = P_53 
instance C_P Ent56 Ent29 where
    _p = P_56 []
    p_  = P_56 
instance C_P Ent59 Ent4 where
    _p = P_59 []
    p_  = P_59 
instance C_P Ent61 Ent60 where
    _p = P_61 []
    p_  = P_61 
instance C_P Ent64 Ent62 where
    _p = P_64 []
    p_  = P_64 
instance C_P Ent65 Ent62 where
    _p = P_65 []
    p_  = P_65 
instance C_P Ent69 Ent71 where
    _p = P_69 []
    p_  = P_69 
instance C_P Ent70 Ent71 where
    _p = P_70 []
    p_  = P_70 
instance C_P Ent75 Ent71 where
    _p = P_75 []
    p_  = P_75 
instance C_P Ent80 Ent62 where
    _p = P_80 []
    p_  = P_80 
instance C_P Ent85 Ent62 where
    _p = P_85 []
    p_  = P_85 
instance C_P Ent86 Ent62 where
    _p = P_86 []
    p_  = P_86 
instance C_P Ent89 Ent62 where
    _p = P_89 []
    p_  = P_89 
instance C_P Ent92 Ent60 where
    _p = P_92 []
    p_  = P_92 
instance C_P Ent93 Ent60 where
    _p = P_93 []
    p_  = P_93 
instance C_P Ent94 Ent60 where
    _p = P_94 []
    p_  = P_94 
instance C_P Ent98 Ent113 where
    _p = P_98 []
    p_  = P_98 
instance C_P Ent100 Ent113 where
    _p = P_100 []
    p_  = P_100 
instance C_P Ent102 Ent13 where
    _p = P_102 []
    p_  = P_102 
instance C_P Ent103 Ent13 where
    _p = P_103 []
    p_  = P_103 
instance C_P Ent105 Ent38 where
    _p = P_105 []
    p_  = P_105 
instance C_P Ent106 Ent38 where
    _p = P_106 []
    p_  = P_106 
instance C_P Ent109 Ent38 where
    _p = P_109 []
    p_  = P_109 
instance C_P Ent112 Ent13 where
    _p = P_112 []
    p_  = P_112 
instance C_P Ent114 Ent113 where
    _p = P_114 []
    p_  = P_114 
instance C_P Ent115 Ent113 where
    _p = P_115 []
    p_  = P_115 
instance C_P Ent117 Ent71 where
    _p = P_117 []
    p_  = P_117 
instance C_P Ent118 Ent71 where
    _p = P_118 []
    p_  = P_118 
instance C_P Ent121 Ent71 where
    _p = P_121 []
    p_  = P_121 
instance C_P Ent124 Ent113 where
    _p = P_124 []
    p_  = P_124 
instance C_P Ent128 Ent113 where
    _p = P_128 []
    p_  = P_128 
instance C_P Ent133 Ent60 where
    _p = P_133 []
    p_  = P_133 

class C_H1 a b | a -> b where
    _h1 :: [b] -> a
    h1_ :: [Att11] -> [b] -> a
instance C_H1 Ent3 Ent60 where
    _h1 = H1_3 []
    h1_  = H1_3 
instance C_H1 Ent6 Ent4 where
    _h1 = H1_6 []
    h1_  = H1_6 
instance C_H1 Ent7 Ent4 where
    _h1 = H1_7 []
    h1_  = H1_7 
instance C_H1 Ent11 Ent13 where
    _h1 = H1_11 []
    h1_  = H1_11 
instance C_H1 Ent12 Ent13 where
    _h1 = H1_12 []
    h1_  = H1_12 
instance C_H1 Ent17 Ent13 where
    _h1 = H1_17 []
    h1_  = H1_17 
instance C_H1 Ent22 Ent4 where
    _h1 = H1_22 []
    h1_  = H1_22 
instance C_H1 Ent27 Ent4 where
    _h1 = H1_27 []
    h1_  = H1_27 
instance C_H1 Ent28 Ent4 where
    _h1 = H1_28 []
    h1_  = H1_28 
instance C_H1 Ent31 Ent29 where
    _h1 = H1_31 []
    h1_  = H1_31 
instance C_H1 Ent32 Ent29 where
    _h1 = H1_32 []
    h1_  = H1_32 
instance C_H1 Ent36 Ent38 where
    _h1 = H1_36 []
    h1_  = H1_36 
instance C_H1 Ent37 Ent38 where
    _h1 = H1_37 []
    h1_  = H1_37 
instance C_H1 Ent42 Ent38 where
    _h1 = H1_42 []
    h1_  = H1_42 
instance C_H1 Ent47 Ent29 where
    _h1 = H1_47 []
    h1_  = H1_47 
instance C_H1 Ent52 Ent29 where
    _h1 = H1_52 []
    h1_  = H1_52 
instance C_H1 Ent53 Ent29 where
    _h1 = H1_53 []
    h1_  = H1_53 
instance C_H1 Ent56 Ent29 where
    _h1 = H1_56 []
    h1_  = H1_56 
instance C_H1 Ent59 Ent4 where
    _h1 = H1_59 []
    h1_  = H1_59 
instance C_H1 Ent61 Ent60 where
    _h1 = H1_61 []
    h1_  = H1_61 
instance C_H1 Ent64 Ent62 where
    _h1 = H1_64 []
    h1_  = H1_64 
instance C_H1 Ent65 Ent62 where
    _h1 = H1_65 []
    h1_  = H1_65 
instance C_H1 Ent69 Ent71 where
    _h1 = H1_69 []
    h1_  = H1_69 
instance C_H1 Ent70 Ent71 where
    _h1 = H1_70 []
    h1_  = H1_70 
instance C_H1 Ent75 Ent71 where
    _h1 = H1_75 []
    h1_  = H1_75 
instance C_H1 Ent80 Ent62 where
    _h1 = H1_80 []
    h1_  = H1_80 
instance C_H1 Ent85 Ent62 where
    _h1 = H1_85 []
    h1_  = H1_85 
instance C_H1 Ent86 Ent62 where
    _h1 = H1_86 []
    h1_  = H1_86 
instance C_H1 Ent89 Ent62 where
    _h1 = H1_89 []
    h1_  = H1_89 
instance C_H1 Ent92 Ent60 where
    _h1 = H1_92 []
    h1_  = H1_92 
instance C_H1 Ent93 Ent60 where
    _h1 = H1_93 []
    h1_  = H1_93 
instance C_H1 Ent94 Ent60 where
    _h1 = H1_94 []
    h1_  = H1_94 
instance C_H1 Ent98 Ent113 where
    _h1 = H1_98 []
    h1_  = H1_98 
instance C_H1 Ent100 Ent113 where
    _h1 = H1_100 []
    h1_  = H1_100 
instance C_H1 Ent102 Ent13 where
    _h1 = H1_102 []
    h1_  = H1_102 
instance C_H1 Ent103 Ent13 where
    _h1 = H1_103 []
    h1_  = H1_103 
instance C_H1 Ent105 Ent38 where
    _h1 = H1_105 []
    h1_  = H1_105 
instance C_H1 Ent106 Ent38 where
    _h1 = H1_106 []
    h1_  = H1_106 
instance C_H1 Ent109 Ent38 where
    _h1 = H1_109 []
    h1_  = H1_109 
instance C_H1 Ent112 Ent13 where
    _h1 = H1_112 []
    h1_  = H1_112 
instance C_H1 Ent114 Ent113 where
    _h1 = H1_114 []
    h1_  = H1_114 
instance C_H1 Ent115 Ent113 where
    _h1 = H1_115 []
    h1_  = H1_115 
instance C_H1 Ent117 Ent71 where
    _h1 = H1_117 []
    h1_  = H1_117 
instance C_H1 Ent118 Ent71 where
    _h1 = H1_118 []
    h1_  = H1_118 
instance C_H1 Ent121 Ent71 where
    _h1 = H1_121 []
    h1_  = H1_121 
instance C_H1 Ent124 Ent113 where
    _h1 = H1_124 []
    h1_  = H1_124 
instance C_H1 Ent128 Ent113 where
    _h1 = H1_128 []
    h1_  = H1_128 
instance C_H1 Ent133 Ent60 where
    _h1 = H1_133 []
    h1_  = H1_133 

class C_H2 a b | a -> b where
    _h2 :: [b] -> a
    h2_ :: [Att11] -> [b] -> a
instance C_H2 Ent3 Ent60 where
    _h2 = H2_3 []
    h2_  = H2_3 
instance C_H2 Ent6 Ent4 where
    _h2 = H2_6 []
    h2_  = H2_6 
instance C_H2 Ent7 Ent4 where
    _h2 = H2_7 []
    h2_  = H2_7 
instance C_H2 Ent11 Ent13 where
    _h2 = H2_11 []
    h2_  = H2_11 
instance C_H2 Ent12 Ent13 where
    _h2 = H2_12 []
    h2_  = H2_12 
instance C_H2 Ent17 Ent13 where
    _h2 = H2_17 []
    h2_  = H2_17 
instance C_H2 Ent22 Ent4 where
    _h2 = H2_22 []
    h2_  = H2_22 
instance C_H2 Ent27 Ent4 where
    _h2 = H2_27 []
    h2_  = H2_27 
instance C_H2 Ent28 Ent4 where
    _h2 = H2_28 []
    h2_  = H2_28 
instance C_H2 Ent31 Ent29 where
    _h2 = H2_31 []
    h2_  = H2_31 
instance C_H2 Ent32 Ent29 where
    _h2 = H2_32 []
    h2_  = H2_32 
instance C_H2 Ent36 Ent38 where
    _h2 = H2_36 []
    h2_  = H2_36 
instance C_H2 Ent37 Ent38 where
    _h2 = H2_37 []
    h2_  = H2_37 
instance C_H2 Ent42 Ent38 where
    _h2 = H2_42 []
    h2_  = H2_42 
instance C_H2 Ent47 Ent29 where
    _h2 = H2_47 []
    h2_  = H2_47 
instance C_H2 Ent52 Ent29 where
    _h2 = H2_52 []
    h2_  = H2_52 
instance C_H2 Ent53 Ent29 where
    _h2 = H2_53 []
    h2_  = H2_53 
instance C_H2 Ent56 Ent29 where
    _h2 = H2_56 []
    h2_  = H2_56 
instance C_H2 Ent59 Ent4 where
    _h2 = H2_59 []
    h2_  = H2_59 
instance C_H2 Ent61 Ent60 where
    _h2 = H2_61 []
    h2_  = H2_61 
instance C_H2 Ent64 Ent62 where
    _h2 = H2_64 []
    h2_  = H2_64 
instance C_H2 Ent65 Ent62 where
    _h2 = H2_65 []
    h2_  = H2_65 
instance C_H2 Ent69 Ent71 where
    _h2 = H2_69 []
    h2_  = H2_69 
instance C_H2 Ent70 Ent71 where
    _h2 = H2_70 []
    h2_  = H2_70 
instance C_H2 Ent75 Ent71 where
    _h2 = H2_75 []
    h2_  = H2_75 
instance C_H2 Ent80 Ent62 where
    _h2 = H2_80 []
    h2_  = H2_80 
instance C_H2 Ent85 Ent62 where
    _h2 = H2_85 []
    h2_  = H2_85 
instance C_H2 Ent86 Ent62 where
    _h2 = H2_86 []
    h2_  = H2_86 
instance C_H2 Ent89 Ent62 where
    _h2 = H2_89 []
    h2_  = H2_89 
instance C_H2 Ent92 Ent60 where
    _h2 = H2_92 []
    h2_  = H2_92 
instance C_H2 Ent93 Ent60 where
    _h2 = H2_93 []
    h2_  = H2_93 
instance C_H2 Ent94 Ent60 where
    _h2 = H2_94 []
    h2_  = H2_94 
instance C_H2 Ent98 Ent113 where
    _h2 = H2_98 []
    h2_  = H2_98 
instance C_H2 Ent100 Ent113 where
    _h2 = H2_100 []
    h2_  = H2_100 
instance C_H2 Ent102 Ent13 where
    _h2 = H2_102 []
    h2_  = H2_102 
instance C_H2 Ent103 Ent13 where
    _h2 = H2_103 []
    h2_  = H2_103 
instance C_H2 Ent105 Ent38 where
    _h2 = H2_105 []
    h2_  = H2_105 
instance C_H2 Ent106 Ent38 where
    _h2 = H2_106 []
    h2_  = H2_106 
instance C_H2 Ent109 Ent38 where
    _h2 = H2_109 []
    h2_  = H2_109 
instance C_H2 Ent112 Ent13 where
    _h2 = H2_112 []
    h2_  = H2_112 
instance C_H2 Ent114 Ent113 where
    _h2 = H2_114 []
    h2_  = H2_114 
instance C_H2 Ent115 Ent113 where
    _h2 = H2_115 []
    h2_  = H2_115 
instance C_H2 Ent117 Ent71 where
    _h2 = H2_117 []
    h2_  = H2_117 
instance C_H2 Ent118 Ent71 where
    _h2 = H2_118 []
    h2_  = H2_118 
instance C_H2 Ent121 Ent71 where
    _h2 = H2_121 []
    h2_  = H2_121 
instance C_H2 Ent124 Ent113 where
    _h2 = H2_124 []
    h2_  = H2_124 
instance C_H2 Ent128 Ent113 where
    _h2 = H2_128 []
    h2_  = H2_128 
instance C_H2 Ent133 Ent60 where
    _h2 = H2_133 []
    h2_  = H2_133 

class C_H3 a b | a -> b where
    _h3 :: [b] -> a
    h3_ :: [Att11] -> [b] -> a
instance C_H3 Ent3 Ent60 where
    _h3 = H3_3 []
    h3_  = H3_3 
instance C_H3 Ent6 Ent4 where
    _h3 = H3_6 []
    h3_  = H3_6 
instance C_H3 Ent7 Ent4 where
    _h3 = H3_7 []
    h3_  = H3_7 
instance C_H3 Ent11 Ent13 where
    _h3 = H3_11 []
    h3_  = H3_11 
instance C_H3 Ent12 Ent13 where
    _h3 = H3_12 []
    h3_  = H3_12 
instance C_H3 Ent17 Ent13 where
    _h3 = H3_17 []
    h3_  = H3_17 
instance C_H3 Ent22 Ent4 where
    _h3 = H3_22 []
    h3_  = H3_22 
instance C_H3 Ent27 Ent4 where
    _h3 = H3_27 []
    h3_  = H3_27 
instance C_H3 Ent28 Ent4 where
    _h3 = H3_28 []
    h3_  = H3_28 
instance C_H3 Ent31 Ent29 where
    _h3 = H3_31 []
    h3_  = H3_31 
instance C_H3 Ent32 Ent29 where
    _h3 = H3_32 []
    h3_  = H3_32 
instance C_H3 Ent36 Ent38 where
    _h3 = H3_36 []
    h3_  = H3_36 
instance C_H3 Ent37 Ent38 where
    _h3 = H3_37 []
    h3_  = H3_37 
instance C_H3 Ent42 Ent38 where
    _h3 = H3_42 []
    h3_  = H3_42 
instance C_H3 Ent47 Ent29 where
    _h3 = H3_47 []
    h3_  = H3_47 
instance C_H3 Ent52 Ent29 where
    _h3 = H3_52 []
    h3_  = H3_52 
instance C_H3 Ent53 Ent29 where
    _h3 = H3_53 []
    h3_  = H3_53 
instance C_H3 Ent56 Ent29 where
    _h3 = H3_56 []
    h3_  = H3_56 
instance C_H3 Ent59 Ent4 where
    _h3 = H3_59 []
    h3_  = H3_59 
instance C_H3 Ent61 Ent60 where
    _h3 = H3_61 []
    h3_  = H3_61 
instance C_H3 Ent64 Ent62 where
    _h3 = H3_64 []
    h3_  = H3_64 
instance C_H3 Ent65 Ent62 where
    _h3 = H3_65 []
    h3_  = H3_65 
instance C_H3 Ent69 Ent71 where
    _h3 = H3_69 []
    h3_  = H3_69 
instance C_H3 Ent70 Ent71 where
    _h3 = H3_70 []
    h3_  = H3_70 
instance C_H3 Ent75 Ent71 where
    _h3 = H3_75 []
    h3_  = H3_75 
instance C_H3 Ent80 Ent62 where
    _h3 = H3_80 []
    h3_  = H3_80 
instance C_H3 Ent85 Ent62 where
    _h3 = H3_85 []
    h3_  = H3_85 
instance C_H3 Ent86 Ent62 where
    _h3 = H3_86 []
    h3_  = H3_86 
instance C_H3 Ent89 Ent62 where
    _h3 = H3_89 []
    h3_  = H3_89 
instance C_H3 Ent92 Ent60 where
    _h3 = H3_92 []
    h3_  = H3_92 
instance C_H3 Ent93 Ent60 where
    _h3 = H3_93 []
    h3_  = H3_93 
instance C_H3 Ent94 Ent60 where
    _h3 = H3_94 []
    h3_  = H3_94 
instance C_H3 Ent98 Ent113 where
    _h3 = H3_98 []
    h3_  = H3_98 
instance C_H3 Ent100 Ent113 where
    _h3 = H3_100 []
    h3_  = H3_100 
instance C_H3 Ent102 Ent13 where
    _h3 = H3_102 []
    h3_  = H3_102 
instance C_H3 Ent103 Ent13 where
    _h3 = H3_103 []
    h3_  = H3_103 
instance C_H3 Ent105 Ent38 where
    _h3 = H3_105 []
    h3_  = H3_105 
instance C_H3 Ent106 Ent38 where
    _h3 = H3_106 []
    h3_  = H3_106 
instance C_H3 Ent109 Ent38 where
    _h3 = H3_109 []
    h3_  = H3_109 
instance C_H3 Ent112 Ent13 where
    _h3 = H3_112 []
    h3_  = H3_112 
instance C_H3 Ent114 Ent113 where
    _h3 = H3_114 []
    h3_  = H3_114 
instance C_H3 Ent115 Ent113 where
    _h3 = H3_115 []
    h3_  = H3_115 
instance C_H3 Ent117 Ent71 where
    _h3 = H3_117 []
    h3_  = H3_117 
instance C_H3 Ent118 Ent71 where
    _h3 = H3_118 []
    h3_  = H3_118 
instance C_H3 Ent121 Ent71 where
    _h3 = H3_121 []
    h3_  = H3_121 
instance C_H3 Ent124 Ent113 where
    _h3 = H3_124 []
    h3_  = H3_124 
instance C_H3 Ent128 Ent113 where
    _h3 = H3_128 []
    h3_  = H3_128 
instance C_H3 Ent133 Ent60 where
    _h3 = H3_133 []
    h3_  = H3_133 

class C_H4 a b | a -> b where
    _h4 :: [b] -> a
    h4_ :: [Att11] -> [b] -> a
instance C_H4 Ent3 Ent60 where
    _h4 = H4_3 []
    h4_  = H4_3 
instance C_H4 Ent6 Ent4 where
    _h4 = H4_6 []
    h4_  = H4_6 
instance C_H4 Ent7 Ent4 where
    _h4 = H4_7 []
    h4_  = H4_7 
instance C_H4 Ent11 Ent13 where
    _h4 = H4_11 []
    h4_  = H4_11 
instance C_H4 Ent12 Ent13 where
    _h4 = H4_12 []
    h4_  = H4_12 
instance C_H4 Ent17 Ent13 where
    _h4 = H4_17 []
    h4_  = H4_17 
instance C_H4 Ent22 Ent4 where
    _h4 = H4_22 []
    h4_  = H4_22 
instance C_H4 Ent27 Ent4 where
    _h4 = H4_27 []
    h4_  = H4_27 
instance C_H4 Ent28 Ent4 where
    _h4 = H4_28 []
    h4_  = H4_28 
instance C_H4 Ent31 Ent29 where
    _h4 = H4_31 []
    h4_  = H4_31 
instance C_H4 Ent32 Ent29 where
    _h4 = H4_32 []
    h4_  = H4_32 
instance C_H4 Ent36 Ent38 where
    _h4 = H4_36 []
    h4_  = H4_36 
instance C_H4 Ent37 Ent38 where
    _h4 = H4_37 []
    h4_  = H4_37 
instance C_H4 Ent42 Ent38 where
    _h4 = H4_42 []
    h4_  = H4_42 
instance C_H4 Ent47 Ent29 where
    _h4 = H4_47 []
    h4_  = H4_47 
instance C_H4 Ent52 Ent29 where
    _h4 = H4_52 []
    h4_  = H4_52 
instance C_H4 Ent53 Ent29 where
    _h4 = H4_53 []
    h4_  = H4_53 
instance C_H4 Ent56 Ent29 where
    _h4 = H4_56 []
    h4_  = H4_56 
instance C_H4 Ent59 Ent4 where
    _h4 = H4_59 []
    h4_  = H4_59 
instance C_H4 Ent61 Ent60 where
    _h4 = H4_61 []
    h4_  = H4_61 
instance C_H4 Ent64 Ent62 where
    _h4 = H4_64 []
    h4_  = H4_64 
instance C_H4 Ent65 Ent62 where
    _h4 = H4_65 []
    h4_  = H4_65 
instance C_H4 Ent69 Ent71 where
    _h4 = H4_69 []
    h4_  = H4_69 
instance C_H4 Ent70 Ent71 where
    _h4 = H4_70 []
    h4_  = H4_70 
instance C_H4 Ent75 Ent71 where
    _h4 = H4_75 []
    h4_  = H4_75 
instance C_H4 Ent80 Ent62 where
    _h4 = H4_80 []
    h4_  = H4_80 
instance C_H4 Ent85 Ent62 where
    _h4 = H4_85 []
    h4_  = H4_85 
instance C_H4 Ent86 Ent62 where
    _h4 = H4_86 []
    h4_  = H4_86 
instance C_H4 Ent89 Ent62 where
    _h4 = H4_89 []
    h4_  = H4_89 
instance C_H4 Ent92 Ent60 where
    _h4 = H4_92 []
    h4_  = H4_92 
instance C_H4 Ent93 Ent60 where
    _h4 = H4_93 []
    h4_  = H4_93 
instance C_H4 Ent94 Ent60 where
    _h4 = H4_94 []
    h4_  = H4_94 
instance C_H4 Ent98 Ent113 where
    _h4 = H4_98 []
    h4_  = H4_98 
instance C_H4 Ent100 Ent113 where
    _h4 = H4_100 []
    h4_  = H4_100 
instance C_H4 Ent102 Ent13 where
    _h4 = H4_102 []
    h4_  = H4_102 
instance C_H4 Ent103 Ent13 where
    _h4 = H4_103 []
    h4_  = H4_103 
instance C_H4 Ent105 Ent38 where
    _h4 = H4_105 []
    h4_  = H4_105 
instance C_H4 Ent106 Ent38 where
    _h4 = H4_106 []
    h4_  = H4_106 
instance C_H4 Ent109 Ent38 where
    _h4 = H4_109 []
    h4_  = H4_109 
instance C_H4 Ent112 Ent13 where
    _h4 = H4_112 []
    h4_  = H4_112 
instance C_H4 Ent114 Ent113 where
    _h4 = H4_114 []
    h4_  = H4_114 
instance C_H4 Ent115 Ent113 where
    _h4 = H4_115 []
    h4_  = H4_115 
instance C_H4 Ent117 Ent71 where
    _h4 = H4_117 []
    h4_  = H4_117 
instance C_H4 Ent118 Ent71 where
    _h4 = H4_118 []
    h4_  = H4_118 
instance C_H4 Ent121 Ent71 where
    _h4 = H4_121 []
    h4_  = H4_121 
instance C_H4 Ent124 Ent113 where
    _h4 = H4_124 []
    h4_  = H4_124 
instance C_H4 Ent128 Ent113 where
    _h4 = H4_128 []
    h4_  = H4_128 
instance C_H4 Ent133 Ent60 where
    _h4 = H4_133 []
    h4_  = H4_133 

class C_H5 a b | a -> b where
    _h5 :: [b] -> a
    h5_ :: [Att11] -> [b] -> a
instance C_H5 Ent3 Ent60 where
    _h5 = H5_3 []
    h5_  = H5_3 
instance C_H5 Ent6 Ent4 where
    _h5 = H5_6 []
    h5_  = H5_6 
instance C_H5 Ent7 Ent4 where
    _h5 = H5_7 []
    h5_  = H5_7 
instance C_H5 Ent11 Ent13 where
    _h5 = H5_11 []
    h5_  = H5_11 
instance C_H5 Ent12 Ent13 where
    _h5 = H5_12 []
    h5_  = H5_12 
instance C_H5 Ent17 Ent13 where
    _h5 = H5_17 []
    h5_  = H5_17 
instance C_H5 Ent22 Ent4 where
    _h5 = H5_22 []
    h5_  = H5_22 
instance C_H5 Ent27 Ent4 where
    _h5 = H5_27 []
    h5_  = H5_27 
instance C_H5 Ent28 Ent4 where
    _h5 = H5_28 []
    h5_  = H5_28 
instance C_H5 Ent31 Ent29 where
    _h5 = H5_31 []
    h5_  = H5_31 
instance C_H5 Ent32 Ent29 where
    _h5 = H5_32 []
    h5_  = H5_32 
instance C_H5 Ent36 Ent38 where
    _h5 = H5_36 []
    h5_  = H5_36 
instance C_H5 Ent37 Ent38 where
    _h5 = H5_37 []
    h5_  = H5_37 
instance C_H5 Ent42 Ent38 where
    _h5 = H5_42 []
    h5_  = H5_42 
instance C_H5 Ent47 Ent29 where
    _h5 = H5_47 []
    h5_  = H5_47 
instance C_H5 Ent52 Ent29 where
    _h5 = H5_52 []
    h5_  = H5_52 
instance C_H5 Ent53 Ent29 where
    _h5 = H5_53 []
    h5_  = H5_53 
instance C_H5 Ent56 Ent29 where
    _h5 = H5_56 []
    h5_  = H5_56 
instance C_H5 Ent59 Ent4 where
    _h5 = H5_59 []
    h5_  = H5_59 
instance C_H5 Ent61 Ent60 where
    _h5 = H5_61 []
    h5_  = H5_61 
instance C_H5 Ent64 Ent62 where
    _h5 = H5_64 []
    h5_  = H5_64 
instance C_H5 Ent65 Ent62 where
    _h5 = H5_65 []
    h5_  = H5_65 
instance C_H5 Ent69 Ent71 where
    _h5 = H5_69 []
    h5_  = H5_69 
instance C_H5 Ent70 Ent71 where
    _h5 = H5_70 []
    h5_  = H5_70 
instance C_H5 Ent75 Ent71 where
    _h5 = H5_75 []
    h5_  = H5_75 
instance C_H5 Ent80 Ent62 where
    _h5 = H5_80 []
    h5_  = H5_80 
instance C_H5 Ent85 Ent62 where
    _h5 = H5_85 []
    h5_  = H5_85 
instance C_H5 Ent86 Ent62 where
    _h5 = H5_86 []
    h5_  = H5_86 
instance C_H5 Ent89 Ent62 where
    _h5 = H5_89 []
    h5_  = H5_89 
instance C_H5 Ent92 Ent60 where
    _h5 = H5_92 []
    h5_  = H5_92 
instance C_H5 Ent93 Ent60 where
    _h5 = H5_93 []
    h5_  = H5_93 
instance C_H5 Ent94 Ent60 where
    _h5 = H5_94 []
    h5_  = H5_94 
instance C_H5 Ent98 Ent113 where
    _h5 = H5_98 []
    h5_  = H5_98 
instance C_H5 Ent100 Ent113 where
    _h5 = H5_100 []
    h5_  = H5_100 
instance C_H5 Ent102 Ent13 where
    _h5 = H5_102 []
    h5_  = H5_102 
instance C_H5 Ent103 Ent13 where
    _h5 = H5_103 []
    h5_  = H5_103 
instance C_H5 Ent105 Ent38 where
    _h5 = H5_105 []
    h5_  = H5_105 
instance C_H5 Ent106 Ent38 where
    _h5 = H5_106 []
    h5_  = H5_106 
instance C_H5 Ent109 Ent38 where
    _h5 = H5_109 []
    h5_  = H5_109 
instance C_H5 Ent112 Ent13 where
    _h5 = H5_112 []
    h5_  = H5_112 
instance C_H5 Ent114 Ent113 where
    _h5 = H5_114 []
    h5_  = H5_114 
instance C_H5 Ent115 Ent113 where
    _h5 = H5_115 []
    h5_  = H5_115 
instance C_H5 Ent117 Ent71 where
    _h5 = H5_117 []
    h5_  = H5_117 
instance C_H5 Ent118 Ent71 where
    _h5 = H5_118 []
    h5_  = H5_118 
instance C_H5 Ent121 Ent71 where
    _h5 = H5_121 []
    h5_  = H5_121 
instance C_H5 Ent124 Ent113 where
    _h5 = H5_124 []
    h5_  = H5_124 
instance C_H5 Ent128 Ent113 where
    _h5 = H5_128 []
    h5_  = H5_128 
instance C_H5 Ent133 Ent60 where
    _h5 = H5_133 []
    h5_  = H5_133 

class C_H6 a b | a -> b where
    _h6 :: [b] -> a
    h6_ :: [Att11] -> [b] -> a
instance C_H6 Ent3 Ent60 where
    _h6 = H6_3 []
    h6_  = H6_3 
instance C_H6 Ent6 Ent4 where
    _h6 = H6_6 []
    h6_  = H6_6 
instance C_H6 Ent7 Ent4 where
    _h6 = H6_7 []
    h6_  = H6_7 
instance C_H6 Ent11 Ent13 where
    _h6 = H6_11 []
    h6_  = H6_11 
instance C_H6 Ent12 Ent13 where
    _h6 = H6_12 []
    h6_  = H6_12 
instance C_H6 Ent17 Ent13 where
    _h6 = H6_17 []
    h6_  = H6_17 
instance C_H6 Ent22 Ent4 where
    _h6 = H6_22 []
    h6_  = H6_22 
instance C_H6 Ent27 Ent4 where
    _h6 = H6_27 []
    h6_  = H6_27 
instance C_H6 Ent28 Ent4 where
    _h6 = H6_28 []
    h6_  = H6_28 
instance C_H6 Ent31 Ent29 where
    _h6 = H6_31 []
    h6_  = H6_31 
instance C_H6 Ent32 Ent29 where
    _h6 = H6_32 []
    h6_  = H6_32 
instance C_H6 Ent36 Ent38 where
    _h6 = H6_36 []
    h6_  = H6_36 
instance C_H6 Ent37 Ent38 where
    _h6 = H6_37 []
    h6_  = H6_37 
instance C_H6 Ent42 Ent38 where
    _h6 = H6_42 []
    h6_  = H6_42 
instance C_H6 Ent47 Ent29 where
    _h6 = H6_47 []
    h6_  = H6_47 
instance C_H6 Ent52 Ent29 where
    _h6 = H6_52 []
    h6_  = H6_52 
instance C_H6 Ent53 Ent29 where
    _h6 = H6_53 []
    h6_  = H6_53 
instance C_H6 Ent56 Ent29 where
    _h6 = H6_56 []
    h6_  = H6_56 
instance C_H6 Ent59 Ent4 where
    _h6 = H6_59 []
    h6_  = H6_59 
instance C_H6 Ent61 Ent60 where
    _h6 = H6_61 []
    h6_  = H6_61 
instance C_H6 Ent64 Ent62 where
    _h6 = H6_64 []
    h6_  = H6_64 
instance C_H6 Ent65 Ent62 where
    _h6 = H6_65 []
    h6_  = H6_65 
instance C_H6 Ent69 Ent71 where
    _h6 = H6_69 []
    h6_  = H6_69 
instance C_H6 Ent70 Ent71 where
    _h6 = H6_70 []
    h6_  = H6_70 
instance C_H6 Ent75 Ent71 where
    _h6 = H6_75 []
    h6_  = H6_75 
instance C_H6 Ent80 Ent62 where
    _h6 = H6_80 []
    h6_  = H6_80 
instance C_H6 Ent85 Ent62 where
    _h6 = H6_85 []
    h6_  = H6_85 
instance C_H6 Ent86 Ent62 where
    _h6 = H6_86 []
    h6_  = H6_86 
instance C_H6 Ent89 Ent62 where
    _h6 = H6_89 []
    h6_  = H6_89 
instance C_H6 Ent92 Ent60 where
    _h6 = H6_92 []
    h6_  = H6_92 
instance C_H6 Ent93 Ent60 where
    _h6 = H6_93 []
    h6_  = H6_93 
instance C_H6 Ent94 Ent60 where
    _h6 = H6_94 []
    h6_  = H6_94 
instance C_H6 Ent98 Ent113 where
    _h6 = H6_98 []
    h6_  = H6_98 
instance C_H6 Ent100 Ent113 where
    _h6 = H6_100 []
    h6_  = H6_100 
instance C_H6 Ent102 Ent13 where
    _h6 = H6_102 []
    h6_  = H6_102 
instance C_H6 Ent103 Ent13 where
    _h6 = H6_103 []
    h6_  = H6_103 
instance C_H6 Ent105 Ent38 where
    _h6 = H6_105 []
    h6_  = H6_105 
instance C_H6 Ent106 Ent38 where
    _h6 = H6_106 []
    h6_  = H6_106 
instance C_H6 Ent109 Ent38 where
    _h6 = H6_109 []
    h6_  = H6_109 
instance C_H6 Ent112 Ent13 where
    _h6 = H6_112 []
    h6_  = H6_112 
instance C_H6 Ent114 Ent113 where
    _h6 = H6_114 []
    h6_  = H6_114 
instance C_H6 Ent115 Ent113 where
    _h6 = H6_115 []
    h6_  = H6_115 
instance C_H6 Ent117 Ent71 where
    _h6 = H6_117 []
    h6_  = H6_117 
instance C_H6 Ent118 Ent71 where
    _h6 = H6_118 []
    h6_  = H6_118 
instance C_H6 Ent121 Ent71 where
    _h6 = H6_121 []
    h6_  = H6_121 
instance C_H6 Ent124 Ent113 where
    _h6 = H6_124 []
    h6_  = H6_124 
instance C_H6 Ent128 Ent113 where
    _h6 = H6_128 []
    h6_  = H6_128 
instance C_H6 Ent133 Ent60 where
    _h6 = H6_133 []
    h6_  = H6_133 

class C_Ul a b | a -> b where
    _ul :: [b] -> a
    ul_ :: [Att11] -> [b] -> a
instance C_Ul Ent3 Ent95 where
    _ul = Ul_3 []
    ul_  = Ul_3 
instance C_Ul Ent6 Ent8 where
    _ul = Ul_6 []
    ul_  = Ul_6 
instance C_Ul Ent7 Ent8 where
    _ul = Ul_7 []
    ul_  = Ul_7 
instance C_Ul Ent11 Ent14 where
    _ul = Ul_11 []
    ul_  = Ul_11 
instance C_Ul Ent12 Ent14 where
    _ul = Ul_12 []
    ul_  = Ul_12 
instance C_Ul Ent17 Ent14 where
    _ul = Ul_17 []
    ul_  = Ul_17 
instance C_Ul Ent22 Ent8 where
    _ul = Ul_22 []
    ul_  = Ul_22 
instance C_Ul Ent27 Ent8 where
    _ul = Ul_27 []
    ul_  = Ul_27 
instance C_Ul Ent28 Ent8 where
    _ul = Ul_28 []
    ul_  = Ul_28 
instance C_Ul Ent31 Ent33 where
    _ul = Ul_31 []
    ul_  = Ul_31 
instance C_Ul Ent32 Ent33 where
    _ul = Ul_32 []
    ul_  = Ul_32 
instance C_Ul Ent36 Ent39 where
    _ul = Ul_36 []
    ul_  = Ul_36 
instance C_Ul Ent37 Ent39 where
    _ul = Ul_37 []
    ul_  = Ul_37 
instance C_Ul Ent42 Ent39 where
    _ul = Ul_42 []
    ul_  = Ul_42 
instance C_Ul Ent47 Ent33 where
    _ul = Ul_47 []
    ul_  = Ul_47 
instance C_Ul Ent52 Ent33 where
    _ul = Ul_52 []
    ul_  = Ul_52 
instance C_Ul Ent53 Ent33 where
    _ul = Ul_53 []
    ul_  = Ul_53 
instance C_Ul Ent56 Ent33 where
    _ul = Ul_56 []
    ul_  = Ul_56 
instance C_Ul Ent59 Ent8 where
    _ul = Ul_59 []
    ul_  = Ul_59 
instance C_Ul Ent61 Ent95 where
    _ul = Ul_61 []
    ul_  = Ul_61 
instance C_Ul Ent64 Ent66 where
    _ul = Ul_64 []
    ul_  = Ul_64 
instance C_Ul Ent65 Ent66 where
    _ul = Ul_65 []
    ul_  = Ul_65 
instance C_Ul Ent69 Ent72 where
    _ul = Ul_69 []
    ul_  = Ul_69 
instance C_Ul Ent70 Ent72 where
    _ul = Ul_70 []
    ul_  = Ul_70 
instance C_Ul Ent75 Ent72 where
    _ul = Ul_75 []
    ul_  = Ul_75 
instance C_Ul Ent80 Ent66 where
    _ul = Ul_80 []
    ul_  = Ul_80 
instance C_Ul Ent85 Ent66 where
    _ul = Ul_85 []
    ul_  = Ul_85 
instance C_Ul Ent86 Ent66 where
    _ul = Ul_86 []
    ul_  = Ul_86 
instance C_Ul Ent89 Ent66 where
    _ul = Ul_89 []
    ul_  = Ul_89 
instance C_Ul Ent92 Ent95 where
    _ul = Ul_92 []
    ul_  = Ul_92 
instance C_Ul Ent93 Ent95 where
    _ul = Ul_93 []
    ul_  = Ul_93 
instance C_Ul Ent94 Ent95 where
    _ul = Ul_94 []
    ul_  = Ul_94 
instance C_Ul Ent98 Ent125 where
    _ul = Ul_98 []
    ul_  = Ul_98 
instance C_Ul Ent100 Ent125 where
    _ul = Ul_100 []
    ul_  = Ul_100 
instance C_Ul Ent102 Ent14 where
    _ul = Ul_102 []
    ul_  = Ul_102 
instance C_Ul Ent103 Ent14 where
    _ul = Ul_103 []
    ul_  = Ul_103 
instance C_Ul Ent105 Ent39 where
    _ul = Ul_105 []
    ul_  = Ul_105 
instance C_Ul Ent106 Ent39 where
    _ul = Ul_106 []
    ul_  = Ul_106 
instance C_Ul Ent109 Ent39 where
    _ul = Ul_109 []
    ul_  = Ul_109 
instance C_Ul Ent112 Ent14 where
    _ul = Ul_112 []
    ul_  = Ul_112 
instance C_Ul Ent114 Ent125 where
    _ul = Ul_114 []
    ul_  = Ul_114 
instance C_Ul Ent115 Ent125 where
    _ul = Ul_115 []
    ul_  = Ul_115 
instance C_Ul Ent117 Ent72 where
    _ul = Ul_117 []
    ul_  = Ul_117 
instance C_Ul Ent118 Ent72 where
    _ul = Ul_118 []
    ul_  = Ul_118 
instance C_Ul Ent121 Ent72 where
    _ul = Ul_121 []
    ul_  = Ul_121 
instance C_Ul Ent124 Ent125 where
    _ul = Ul_124 []
    ul_  = Ul_124 
instance C_Ul Ent128 Ent125 where
    _ul = Ul_128 []
    ul_  = Ul_128 
instance C_Ul Ent133 Ent95 where
    _ul = Ul_133 []
    ul_  = Ul_133 

class C_Ol a b | a -> b where
    _ol :: [b] -> a
    ol_ :: [Att11] -> [b] -> a
instance C_Ol Ent3 Ent95 where
    _ol = Ol_3 []
    ol_  = Ol_3 
instance C_Ol Ent6 Ent8 where
    _ol = Ol_6 []
    ol_  = Ol_6 
instance C_Ol Ent7 Ent8 where
    _ol = Ol_7 []
    ol_  = Ol_7 
instance C_Ol Ent11 Ent14 where
    _ol = Ol_11 []
    ol_  = Ol_11 
instance C_Ol Ent12 Ent14 where
    _ol = Ol_12 []
    ol_  = Ol_12 
instance C_Ol Ent17 Ent14 where
    _ol = Ol_17 []
    ol_  = Ol_17 
instance C_Ol Ent22 Ent8 where
    _ol = Ol_22 []
    ol_  = Ol_22 
instance C_Ol Ent27 Ent8 where
    _ol = Ol_27 []
    ol_  = Ol_27 
instance C_Ol Ent28 Ent8 where
    _ol = Ol_28 []
    ol_  = Ol_28 
instance C_Ol Ent31 Ent33 where
    _ol = Ol_31 []
    ol_  = Ol_31 
instance C_Ol Ent32 Ent33 where
    _ol = Ol_32 []
    ol_  = Ol_32 
instance C_Ol Ent36 Ent39 where
    _ol = Ol_36 []
    ol_  = Ol_36 
instance C_Ol Ent37 Ent39 where
    _ol = Ol_37 []
    ol_  = Ol_37 
instance C_Ol Ent42 Ent39 where
    _ol = Ol_42 []
    ol_  = Ol_42 
instance C_Ol Ent47 Ent33 where
    _ol = Ol_47 []
    ol_  = Ol_47 
instance C_Ol Ent52 Ent33 where
    _ol = Ol_52 []
    ol_  = Ol_52 
instance C_Ol Ent53 Ent33 where
    _ol = Ol_53 []
    ol_  = Ol_53 
instance C_Ol Ent56 Ent33 where
    _ol = Ol_56 []
    ol_  = Ol_56 
instance C_Ol Ent59 Ent8 where
    _ol = Ol_59 []
    ol_  = Ol_59 
instance C_Ol Ent61 Ent95 where
    _ol = Ol_61 []
    ol_  = Ol_61 
instance C_Ol Ent64 Ent66 where
    _ol = Ol_64 []
    ol_  = Ol_64 
instance C_Ol Ent65 Ent66 where
    _ol = Ol_65 []
    ol_  = Ol_65 
instance C_Ol Ent69 Ent72 where
    _ol = Ol_69 []
    ol_  = Ol_69 
instance C_Ol Ent70 Ent72 where
    _ol = Ol_70 []
    ol_  = Ol_70 
instance C_Ol Ent75 Ent72 where
    _ol = Ol_75 []
    ol_  = Ol_75 
instance C_Ol Ent80 Ent66 where
    _ol = Ol_80 []
    ol_  = Ol_80 
instance C_Ol Ent85 Ent66 where
    _ol = Ol_85 []
    ol_  = Ol_85 
instance C_Ol Ent86 Ent66 where
    _ol = Ol_86 []
    ol_  = Ol_86 
instance C_Ol Ent89 Ent66 where
    _ol = Ol_89 []
    ol_  = Ol_89 
instance C_Ol Ent92 Ent95 where
    _ol = Ol_92 []
    ol_  = Ol_92 
instance C_Ol Ent93 Ent95 where
    _ol = Ol_93 []
    ol_  = Ol_93 
instance C_Ol Ent94 Ent95 where
    _ol = Ol_94 []
    ol_  = Ol_94 
instance C_Ol Ent98 Ent125 where
    _ol = Ol_98 []
    ol_  = Ol_98 
instance C_Ol Ent100 Ent125 where
    _ol = Ol_100 []
    ol_  = Ol_100 
instance C_Ol Ent102 Ent14 where
    _ol = Ol_102 []
    ol_  = Ol_102 
instance C_Ol Ent103 Ent14 where
    _ol = Ol_103 []
    ol_  = Ol_103 
instance C_Ol Ent105 Ent39 where
    _ol = Ol_105 []
    ol_  = Ol_105 
instance C_Ol Ent106 Ent39 where
    _ol = Ol_106 []
    ol_  = Ol_106 
instance C_Ol Ent109 Ent39 where
    _ol = Ol_109 []
    ol_  = Ol_109 
instance C_Ol Ent112 Ent14 where
    _ol = Ol_112 []
    ol_  = Ol_112 
instance C_Ol Ent114 Ent125 where
    _ol = Ol_114 []
    ol_  = Ol_114 
instance C_Ol Ent115 Ent125 where
    _ol = Ol_115 []
    ol_  = Ol_115 
instance C_Ol Ent117 Ent72 where
    _ol = Ol_117 []
    ol_  = Ol_117 
instance C_Ol Ent118 Ent72 where
    _ol = Ol_118 []
    ol_  = Ol_118 
instance C_Ol Ent121 Ent72 where
    _ol = Ol_121 []
    ol_  = Ol_121 
instance C_Ol Ent124 Ent125 where
    _ol = Ol_124 []
    ol_  = Ol_124 
instance C_Ol Ent128 Ent125 where
    _ol = Ol_128 []
    ol_  = Ol_128 
instance C_Ol Ent133 Ent95 where
    _ol = Ol_133 []
    ol_  = Ol_133 

class C_Li a b | a -> b where
    _li :: [b] -> a
    li_ :: [Att11] -> [b] -> a
instance C_Li Ent8 Ent6 where
    _li = Li_8 []
    li_  = Li_8 
instance C_Li Ent14 Ent12 where
    _li = Li_14 []
    li_  = Li_14 
instance C_Li Ent33 Ent31 where
    _li = Li_33 []
    li_  = Li_33 
instance C_Li Ent39 Ent37 where
    _li = Li_39 []
    li_  = Li_39 
instance C_Li Ent66 Ent64 where
    _li = Li_66 []
    li_  = Li_66 
instance C_Li Ent72 Ent70 where
    _li = Li_72 []
    li_  = Li_72 
instance C_Li Ent95 Ent94 where
    _li = Li_95 []
    li_  = Li_95 
instance C_Li Ent125 Ent100 where
    _li = Li_125 []
    li_  = Li_125 

class C_Dl a b | a -> b where
    _dl :: [b] -> a
    dl_ :: [Att11] -> [b] -> a
instance C_Dl Ent3 Ent96 where
    _dl = Dl_3 []
    dl_  = Dl_3 
instance C_Dl Ent6 Ent9 where
    _dl = Dl_6 []
    dl_  = Dl_6 
instance C_Dl Ent7 Ent9 where
    _dl = Dl_7 []
    dl_  = Dl_7 
instance C_Dl Ent11 Ent15 where
    _dl = Dl_11 []
    dl_  = Dl_11 
instance C_Dl Ent12 Ent15 where
    _dl = Dl_12 []
    dl_  = Dl_12 
instance C_Dl Ent17 Ent15 where
    _dl = Dl_17 []
    dl_  = Dl_17 
instance C_Dl Ent22 Ent9 where
    _dl = Dl_22 []
    dl_  = Dl_22 
instance C_Dl Ent27 Ent9 where
    _dl = Dl_27 []
    dl_  = Dl_27 
instance C_Dl Ent28 Ent9 where
    _dl = Dl_28 []
    dl_  = Dl_28 
instance C_Dl Ent31 Ent34 where
    _dl = Dl_31 []
    dl_  = Dl_31 
instance C_Dl Ent32 Ent34 where
    _dl = Dl_32 []
    dl_  = Dl_32 
instance C_Dl Ent36 Ent40 where
    _dl = Dl_36 []
    dl_  = Dl_36 
instance C_Dl Ent37 Ent40 where
    _dl = Dl_37 []
    dl_  = Dl_37 
instance C_Dl Ent42 Ent40 where
    _dl = Dl_42 []
    dl_  = Dl_42 
instance C_Dl Ent47 Ent34 where
    _dl = Dl_47 []
    dl_  = Dl_47 
instance C_Dl Ent52 Ent34 where
    _dl = Dl_52 []
    dl_  = Dl_52 
instance C_Dl Ent53 Ent34 where
    _dl = Dl_53 []
    dl_  = Dl_53 
instance C_Dl Ent56 Ent34 where
    _dl = Dl_56 []
    dl_  = Dl_56 
instance C_Dl Ent59 Ent9 where
    _dl = Dl_59 []
    dl_  = Dl_59 
instance C_Dl Ent61 Ent96 where
    _dl = Dl_61 []
    dl_  = Dl_61 
instance C_Dl Ent64 Ent67 where
    _dl = Dl_64 []
    dl_  = Dl_64 
instance C_Dl Ent65 Ent67 where
    _dl = Dl_65 []
    dl_  = Dl_65 
instance C_Dl Ent69 Ent73 where
    _dl = Dl_69 []
    dl_  = Dl_69 
instance C_Dl Ent70 Ent73 where
    _dl = Dl_70 []
    dl_  = Dl_70 
instance C_Dl Ent75 Ent73 where
    _dl = Dl_75 []
    dl_  = Dl_75 
instance C_Dl Ent80 Ent67 where
    _dl = Dl_80 []
    dl_  = Dl_80 
instance C_Dl Ent85 Ent67 where
    _dl = Dl_85 []
    dl_  = Dl_85 
instance C_Dl Ent86 Ent67 where
    _dl = Dl_86 []
    dl_  = Dl_86 
instance C_Dl Ent89 Ent67 where
    _dl = Dl_89 []
    dl_  = Dl_89 
instance C_Dl Ent92 Ent96 where
    _dl = Dl_92 []
    dl_  = Dl_92 
instance C_Dl Ent93 Ent96 where
    _dl = Dl_93 []
    dl_  = Dl_93 
instance C_Dl Ent94 Ent96 where
    _dl = Dl_94 []
    dl_  = Dl_94 
instance C_Dl Ent98 Ent126 where
    _dl = Dl_98 []
    dl_  = Dl_98 
instance C_Dl Ent100 Ent126 where
    _dl = Dl_100 []
    dl_  = Dl_100 
instance C_Dl Ent102 Ent15 where
    _dl = Dl_102 []
    dl_  = Dl_102 
instance C_Dl Ent103 Ent15 where
    _dl = Dl_103 []
    dl_  = Dl_103 
instance C_Dl Ent105 Ent40 where
    _dl = Dl_105 []
    dl_  = Dl_105 
instance C_Dl Ent106 Ent40 where
    _dl = Dl_106 []
    dl_  = Dl_106 
instance C_Dl Ent109 Ent40 where
    _dl = Dl_109 []
    dl_  = Dl_109 
instance C_Dl Ent112 Ent15 where
    _dl = Dl_112 []
    dl_  = Dl_112 
instance C_Dl Ent114 Ent126 where
    _dl = Dl_114 []
    dl_  = Dl_114 
instance C_Dl Ent115 Ent126 where
    _dl = Dl_115 []
    dl_  = Dl_115 
instance C_Dl Ent117 Ent73 where
    _dl = Dl_117 []
    dl_  = Dl_117 
instance C_Dl Ent118 Ent73 where
    _dl = Dl_118 []
    dl_  = Dl_118 
instance C_Dl Ent121 Ent73 where
    _dl = Dl_121 []
    dl_  = Dl_121 
instance C_Dl Ent124 Ent126 where
    _dl = Dl_124 []
    dl_  = Dl_124 
instance C_Dl Ent128 Ent126 where
    _dl = Dl_128 []
    dl_  = Dl_128 
instance C_Dl Ent133 Ent96 where
    _dl = Dl_133 []
    dl_  = Dl_133 

class C_Dt a b | a -> b where
    _dt :: [b] -> a
    dt_ :: [Att11] -> [b] -> a
instance C_Dt Ent9 Ent4 where
    _dt = Dt_9 []
    dt_  = Dt_9 
instance C_Dt Ent15 Ent13 where
    _dt = Dt_15 []
    dt_  = Dt_15 
instance C_Dt Ent34 Ent29 where
    _dt = Dt_34 []
    dt_  = Dt_34 
instance C_Dt Ent40 Ent38 where
    _dt = Dt_40 []
    dt_  = Dt_40 
instance C_Dt Ent67 Ent62 where
    _dt = Dt_67 []
    dt_  = Dt_67 
instance C_Dt Ent73 Ent71 where
    _dt = Dt_73 []
    dt_  = Dt_73 
instance C_Dt Ent96 Ent60 where
    _dt = Dt_96 []
    dt_  = Dt_96 
instance C_Dt Ent126 Ent113 where
    _dt = Dt_126 []
    dt_  = Dt_126 

class C_Dd a b | a -> b where
    _dd :: [b] -> a
    dd_ :: [Att11] -> [b] -> a
instance C_Dd Ent9 Ent6 where
    _dd = Dd_9 []
    dd_  = Dd_9 
instance C_Dd Ent15 Ent12 where
    _dd = Dd_15 []
    dd_  = Dd_15 
instance C_Dd Ent34 Ent31 where
    _dd = Dd_34 []
    dd_  = Dd_34 
instance C_Dd Ent40 Ent37 where
    _dd = Dd_40 []
    dd_  = Dd_40 
instance C_Dd Ent67 Ent64 where
    _dd = Dd_67 []
    dd_  = Dd_67 
instance C_Dd Ent73 Ent70 where
    _dd = Dd_73 []
    dd_  = Dd_73 
instance C_Dd Ent96 Ent94 where
    _dd = Dd_96 []
    dd_  = Dd_96 
instance C_Dd Ent126 Ent100 where
    _dd = Dd_126 []
    dd_  = Dd_126 

class C_Address a b | a -> b where
    _address :: [b] -> a
    address_ :: [Att11] -> [b] -> a
instance C_Address Ent3 Ent60 where
    _address = Address_3 []
    address_  = Address_3 
instance C_Address Ent6 Ent4 where
    _address = Address_6 []
    address_  = Address_6 
instance C_Address Ent7 Ent4 where
    _address = Address_7 []
    address_  = Address_7 
instance C_Address Ent11 Ent13 where
    _address = Address_11 []
    address_  = Address_11 
instance C_Address Ent12 Ent13 where
    _address = Address_12 []
    address_  = Address_12 
instance C_Address Ent17 Ent13 where
    _address = Address_17 []
    address_  = Address_17 
instance C_Address Ent22 Ent4 where
    _address = Address_22 []
    address_  = Address_22 
instance C_Address Ent27 Ent4 where
    _address = Address_27 []
    address_  = Address_27 
instance C_Address Ent28 Ent4 where
    _address = Address_28 []
    address_  = Address_28 
instance C_Address Ent31 Ent29 where
    _address = Address_31 []
    address_  = Address_31 
instance C_Address Ent32 Ent29 where
    _address = Address_32 []
    address_  = Address_32 
instance C_Address Ent36 Ent38 where
    _address = Address_36 []
    address_  = Address_36 
instance C_Address Ent37 Ent38 where
    _address = Address_37 []
    address_  = Address_37 
instance C_Address Ent42 Ent38 where
    _address = Address_42 []
    address_  = Address_42 
instance C_Address Ent47 Ent29 where
    _address = Address_47 []
    address_  = Address_47 
instance C_Address Ent52 Ent29 where
    _address = Address_52 []
    address_  = Address_52 
instance C_Address Ent53 Ent29 where
    _address = Address_53 []
    address_  = Address_53 
instance C_Address Ent56 Ent29 where
    _address = Address_56 []
    address_  = Address_56 
instance C_Address Ent59 Ent4 where
    _address = Address_59 []
    address_  = Address_59 
instance C_Address Ent61 Ent60 where
    _address = Address_61 []
    address_  = Address_61 
instance C_Address Ent64 Ent62 where
    _address = Address_64 []
    address_  = Address_64 
instance C_Address Ent65 Ent62 where
    _address = Address_65 []
    address_  = Address_65 
instance C_Address Ent69 Ent71 where
    _address = Address_69 []
    address_  = Address_69 
instance C_Address Ent70 Ent71 where
    _address = Address_70 []
    address_  = Address_70 
instance C_Address Ent75 Ent71 where
    _address = Address_75 []
    address_  = Address_75 
instance C_Address Ent80 Ent62 where
    _address = Address_80 []
    address_  = Address_80 
instance C_Address Ent85 Ent62 where
    _address = Address_85 []
    address_  = Address_85 
instance C_Address Ent86 Ent62 where
    _address = Address_86 []
    address_  = Address_86 
instance C_Address Ent89 Ent62 where
    _address = Address_89 []
    address_  = Address_89 
instance C_Address Ent92 Ent60 where
    _address = Address_92 []
    address_  = Address_92 
instance C_Address Ent93 Ent60 where
    _address = Address_93 []
    address_  = Address_93 
instance C_Address Ent94 Ent60 where
    _address = Address_94 []
    address_  = Address_94 
instance C_Address Ent98 Ent113 where
    _address = Address_98 []
    address_  = Address_98 
instance C_Address Ent100 Ent113 where
    _address = Address_100 []
    address_  = Address_100 
instance C_Address Ent102 Ent13 where
    _address = Address_102 []
    address_  = Address_102 
instance C_Address Ent103 Ent13 where
    _address = Address_103 []
    address_  = Address_103 
instance C_Address Ent105 Ent38 where
    _address = Address_105 []
    address_  = Address_105 
instance C_Address Ent106 Ent38 where
    _address = Address_106 []
    address_  = Address_106 
instance C_Address Ent109 Ent38 where
    _address = Address_109 []
    address_  = Address_109 
instance C_Address Ent112 Ent13 where
    _address = Address_112 []
    address_  = Address_112 
instance C_Address Ent114 Ent113 where
    _address = Address_114 []
    address_  = Address_114 
instance C_Address Ent115 Ent113 where
    _address = Address_115 []
    address_  = Address_115 
instance C_Address Ent117 Ent71 where
    _address = Address_117 []
    address_  = Address_117 
instance C_Address Ent118 Ent71 where
    _address = Address_118 []
    address_  = Address_118 
instance C_Address Ent121 Ent71 where
    _address = Address_121 []
    address_  = Address_121 
instance C_Address Ent124 Ent113 where
    _address = Address_124 []
    address_  = Address_124 
instance C_Address Ent128 Ent113 where
    _address = Address_128 []
    address_  = Address_128 
instance C_Address Ent133 Ent60 where
    _address = Address_133 []
    address_  = Address_133 

class C_Hr a where
    _hr :: a
    hr_ :: [Att11] -> a
instance C_Hr Ent3 where
    _hr = Hr_3 []
    hr_ = Hr_3 
instance C_Hr Ent6 where
    _hr = Hr_6 []
    hr_ = Hr_6 
instance C_Hr Ent7 where
    _hr = Hr_7 []
    hr_ = Hr_7 
instance C_Hr Ent11 where
    _hr = Hr_11 []
    hr_ = Hr_11 
instance C_Hr Ent12 where
    _hr = Hr_12 []
    hr_ = Hr_12 
instance C_Hr Ent17 where
    _hr = Hr_17 []
    hr_ = Hr_17 
instance C_Hr Ent22 where
    _hr = Hr_22 []
    hr_ = Hr_22 
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 Ent31 where
    _hr = Hr_31 []
    hr_ = Hr_31 
instance C_Hr Ent32 where
    _hr = Hr_32 []
    hr_ = Hr_32 
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 Ent42 where
    _hr = Hr_42 []
    hr_ = Hr_42 
instance C_Hr Ent47 where
    _hr = Hr_47 []
    hr_ = Hr_47 
instance C_Hr Ent52 where
    _hr = Hr_52 []
    hr_ = Hr_52 
instance C_Hr Ent53 where
    _hr = Hr_53 []
    hr_ = Hr_53 
instance C_Hr Ent56 where
    _hr = Hr_56 []
    hr_ = Hr_56 
instance C_Hr Ent59 where
    _hr = Hr_59 []
    hr_ = Hr_59 
instance C_Hr Ent61 where
    _hr = Hr_61 []
    hr_ = Hr_61 
instance C_Hr Ent64 where
    _hr = Hr_64 []
    hr_ = Hr_64 
instance C_Hr Ent65 where
    _hr = Hr_65 []
    hr_ = Hr_65 
instance C_Hr Ent69 where
    _hr = Hr_69 []
    hr_ = Hr_69 
instance C_Hr Ent70 where
    _hr = Hr_70 []
    hr_ = Hr_70 
instance C_Hr Ent75 where
    _hr = Hr_75 []
    hr_ = Hr_75 
instance C_Hr Ent80 where
    _hr = Hr_80 []
    hr_ = Hr_80 
instance C_Hr Ent85 where
    _hr = Hr_85 []
    hr_ = Hr_85 
instance C_Hr Ent86 where
    _hr = Hr_86 []
    hr_ = Hr_86 
instance C_Hr Ent89 where
    _hr = Hr_89 []
    hr_ = Hr_89 
instance C_Hr Ent92 where
    _hr = Hr_92 []
    hr_ = Hr_92 
instance C_Hr Ent93 where
    _hr = Hr_93 []
    hr_ = Hr_93 
instance C_Hr Ent94 where
    _hr = Hr_94 []
    hr_ = Hr_94 
instance C_Hr Ent98 where
    _hr = Hr_98 []
    hr_ = Hr_98 
instance C_Hr Ent100 where
    _hr = Hr_100 []
    hr_ = Hr_100 
instance C_Hr Ent102 where
    _hr = Hr_102 []
    hr_ = Hr_102 
instance C_Hr Ent103 where
    _hr = Hr_103 []
    hr_ = Hr_103 
instance C_Hr Ent105 where
    _hr = Hr_105 []
    hr_ = Hr_105 
instance C_Hr Ent106 where
    _hr = Hr_106 []
    hr_ = Hr_106 
instance C_Hr Ent109 where
    _hr = Hr_109 []
    hr_ = Hr_109 
instance C_Hr Ent112 where
    _hr = Hr_112 []
    hr_ = Hr_112 
instance C_Hr Ent114 where
    _hr = Hr_114 []
    hr_ = Hr_114 
instance C_Hr Ent115 where
    _hr = Hr_115 []
    hr_ = Hr_115 
instance C_Hr Ent117 where
    _hr = Hr_117 []
    hr_ = Hr_117 
instance C_Hr Ent118 where
    _hr = Hr_118 []
    hr_ = Hr_118 
instance C_Hr Ent121 where
    _hr = Hr_121 []
    hr_ = Hr_121 
instance C_Hr Ent124 where
    _hr = Hr_124 []
    hr_ = Hr_124 
instance C_Hr Ent128 where
    _hr = Hr_128 []
    hr_ = Hr_128 
instance C_Hr Ent133 where
    _hr = Hr_133 []
    hr_ = Hr_133 

class C_Pre a b | a -> b where
    _pre :: [b] -> a
    pre_ :: [Att11] -> [b] -> a
instance C_Pre Ent3 Ent97 where
    _pre = Pre_3 []
    pre_  = Pre_3 
instance C_Pre Ent6 Ent10 where
    _pre = Pre_6 []
    pre_  = Pre_6 
instance C_Pre Ent7 Ent10 where
    _pre = Pre_7 []
    pre_  = Pre_7 
instance C_Pre Ent11 Ent16 where
    _pre = Pre_11 []
    pre_  = Pre_11 
instance C_Pre Ent12 Ent16 where
    _pre = Pre_12 []
    pre_  = Pre_12 
instance C_Pre Ent17 Ent16 where
    _pre = Pre_17 []
    pre_  = Pre_17 
instance C_Pre Ent22 Ent10 where
    _pre = Pre_22 []
    pre_  = Pre_22 
instance C_Pre Ent27 Ent10 where
    _pre = Pre_27 []
    pre_  = Pre_27 
instance C_Pre Ent28 Ent10 where
    _pre = Pre_28 []
    pre_  = Pre_28 
instance C_Pre Ent31 Ent35 where
    _pre = Pre_31 []
    pre_  = Pre_31 
instance C_Pre Ent32 Ent35 where
    _pre = Pre_32 []
    pre_  = Pre_32 
instance C_Pre Ent36 Ent41 where
    _pre = Pre_36 []
    pre_  = Pre_36 
instance C_Pre Ent37 Ent41 where
    _pre = Pre_37 []
    pre_  = Pre_37 
instance C_Pre Ent42 Ent41 where
    _pre = Pre_42 []
    pre_  = Pre_42 
instance C_Pre Ent47 Ent35 where
    _pre = Pre_47 []
    pre_  = Pre_47 
instance C_Pre Ent52 Ent35 where
    _pre = Pre_52 []
    pre_  = Pre_52 
instance C_Pre Ent53 Ent35 where
    _pre = Pre_53 []
    pre_  = Pre_53 
instance C_Pre Ent56 Ent35 where
    _pre = Pre_56 []
    pre_  = Pre_56 
instance C_Pre Ent59 Ent10 where
    _pre = Pre_59 []
    pre_  = Pre_59 
instance C_Pre Ent61 Ent97 where
    _pre = Pre_61 []
    pre_  = Pre_61 
instance C_Pre Ent64 Ent68 where
    _pre = Pre_64 []
    pre_  = Pre_64 
instance C_Pre Ent65 Ent68 where
    _pre = Pre_65 []
    pre_  = Pre_65 
instance C_Pre Ent69 Ent74 where
    _pre = Pre_69 []
    pre_  = Pre_69 
instance C_Pre Ent70 Ent74 where
    _pre = Pre_70 []
    pre_  = Pre_70 
instance C_Pre Ent75 Ent74 where
    _pre = Pre_75 []
    pre_  = Pre_75 
instance C_Pre Ent80 Ent68 where
    _pre = Pre_80 []
    pre_  = Pre_80 
instance C_Pre Ent85 Ent68 where
    _pre = Pre_85 []
    pre_  = Pre_85 
instance C_Pre Ent86 Ent68 where
    _pre = Pre_86 []
    pre_  = Pre_86 
instance C_Pre Ent89 Ent68 where
    _pre = Pre_89 []
    pre_  = Pre_89 
instance C_Pre Ent92 Ent97 where
    _pre = Pre_92 []
    pre_  = Pre_92 
instance C_Pre Ent93 Ent97 where
    _pre = Pre_93 []
    pre_  = Pre_93 
instance C_Pre Ent94 Ent97 where
    _pre = Pre_94 []
    pre_  = Pre_94 
instance C_Pre Ent98 Ent127 where
    _pre = Pre_98 []
    pre_  = Pre_98 
instance C_Pre Ent100 Ent127 where
    _pre = Pre_100 []
    pre_  = Pre_100 
instance C_Pre Ent102 Ent16 where
    _pre = Pre_102 []
    pre_  = Pre_102 
instance C_Pre Ent103 Ent16 where
    _pre = Pre_103 []
    pre_  = Pre_103 
instance C_Pre Ent105 Ent41 where
    _pre = Pre_105 []
    pre_  = Pre_105 
instance C_Pre Ent106 Ent41 where
    _pre = Pre_106 []
    pre_  = Pre_106 
instance C_Pre Ent109 Ent41 where
    _pre = Pre_109 []
    pre_  = Pre_109 
instance C_Pre Ent112 Ent16 where
    _pre = Pre_112 []
    pre_  = Pre_112 
instance C_Pre Ent114 Ent127 where
    _pre = Pre_114 []
    pre_  = Pre_114 
instance C_Pre Ent115 Ent127 where
    _pre = Pre_115 []
    pre_  = Pre_115 
instance C_Pre Ent117 Ent74 where
    _pre = Pre_117 []
    pre_  = Pre_117 
instance C_Pre Ent118 Ent74 where
    _pre = Pre_118 []
    pre_  = Pre_118 
instance C_Pre Ent121 Ent74 where
    _pre = Pre_121 []
    pre_  = Pre_121 
instance C_Pre Ent124 Ent127 where
    _pre = Pre_124 []
    pre_  = Pre_124 
instance C_Pre Ent128 Ent127 where
    _pre = Pre_128 []
    pre_  = Pre_128 
instance C_Pre Ent133 Ent97 where
    _pre = Pre_133 []
    pre_  = Pre_133 

class C_Blockquote a b | a -> b where
    _blockquote :: [b] -> a
    blockquote_ :: [Att13] -> [b] -> a
instance C_Blockquote Ent3 Ent93 where
    _blockquote = Blockquote_3 []
    blockquote_  = Blockquote_3 
instance C_Blockquote Ent6 Ent7 where
    _blockquote = Blockquote_6 []
    blockquote_  = Blockquote_6 
instance C_Blockquote Ent7 Ent7 where
    _blockquote = Blockquote_7 []
    blockquote_  = Blockquote_7 
instance C_Blockquote Ent11 Ent11 where
    _blockquote = Blockquote_11 []
    blockquote_  = Blockquote_11 
instance C_Blockquote Ent12 Ent11 where
    _blockquote = Blockquote_12 []
    blockquote_  = Blockquote_12 
instance C_Blockquote Ent17 Ent11 where
    _blockquote = Blockquote_17 []
    blockquote_  = Blockquote_17 
instance C_Blockquote Ent22 Ent7 where
    _blockquote = Blockquote_22 []
    blockquote_  = Blockquote_22 
instance C_Blockquote Ent27 Ent7 where
    _blockquote = Blockquote_27 []
    blockquote_  = Blockquote_27 
instance C_Blockquote Ent28 Ent7 where
    _blockquote = Blockquote_28 []
    blockquote_  = Blockquote_28 
instance C_Blockquote Ent31 Ent32 where
    _blockquote = Blockquote_31 []
    blockquote_  = Blockquote_31 
instance C_Blockquote Ent32 Ent32 where
    _blockquote = Blockquote_32 []
    blockquote_  = Blockquote_32 
instance C_Blockquote Ent36 Ent36 where
    _blockquote = Blockquote_36 []
    blockquote_  = Blockquote_36 
instance C_Blockquote Ent37 Ent36 where
    _blockquote = Blockquote_37 []
    blockquote_  = Blockquote_37 
instance C_Blockquote Ent42 Ent36 where
    _blockquote = Blockquote_42 []
    blockquote_  = Blockquote_42 
instance C_Blockquote Ent47 Ent32 where
    _blockquote = Blockquote_47 []
    blockquote_  = Blockquote_47 
instance C_Blockquote Ent52 Ent32 where
    _blockquote = Blockquote_52 []
    blockquote_  = Blockquote_52 
instance C_Blockquote Ent53 Ent32 where
    _blockquote = Blockquote_53 []
    blockquote_  = Blockquote_53 
instance C_Blockquote Ent56 Ent32 where
    _blockquote = Blockquote_56 []
    blockquote_  = Blockquote_56 
instance C_Blockquote Ent59 Ent7 where
    _blockquote = Blockquote_59 []
    blockquote_  = Blockquote_59 
instance C_Blockquote Ent61 Ent93 where
    _blockquote = Blockquote_61 []
    blockquote_  = Blockquote_61 
instance C_Blockquote Ent64 Ent65 where
    _blockquote = Blockquote_64 []
    blockquote_  = Blockquote_64 
instance C_Blockquote Ent65 Ent65 where
    _blockquote = Blockquote_65 []
    blockquote_  = Blockquote_65 
instance C_Blockquote Ent69 Ent69 where
    _blockquote = Blockquote_69 []
    blockquote_  = Blockquote_69 
instance C_Blockquote Ent70 Ent69 where
    _blockquote = Blockquote_70 []
    blockquote_  = Blockquote_70 
instance C_Blockquote Ent75 Ent69 where
    _blockquote = Blockquote_75 []
    blockquote_  = Blockquote_75 
instance C_Blockquote Ent80 Ent65 where
    _blockquote = Blockquote_80 []
    blockquote_  = Blockquote_80 
instance C_Blockquote Ent85 Ent65 where
    _blockquote = Blockquote_85 []
    blockquote_  = Blockquote_85 
instance C_Blockquote Ent86 Ent65 where
    _blockquote = Blockquote_86 []
    blockquote_  = Blockquote_86 
instance C_Blockquote Ent89 Ent65 where
    _blockquote = Blockquote_89 []
    blockquote_  = Blockquote_89 
instance C_Blockquote Ent92 Ent93 where
    _blockquote = Blockquote_92 []
    blockquote_  = Blockquote_92 
instance C_Blockquote Ent93 Ent93 where
    _blockquote = Blockquote_93 []
    blockquote_  = Blockquote_93 
instance C_Blockquote Ent94 Ent93 where
    _blockquote = Blockquote_94 []
    blockquote_  = Blockquote_94 
instance C_Blockquote Ent98 Ent98 where
    _blockquote = Blockquote_98 []
    blockquote_  = Blockquote_98 
instance C_Blockquote Ent100 Ent98 where
    _blockquote = Blockquote_100 []
    blockquote_  = Blockquote_100 
instance C_Blockquote Ent102 Ent11 where
    _blockquote = Blockquote_102 []
    blockquote_  = Blockquote_102 
instance C_Blockquote Ent103 Ent11 where
    _blockquote = Blockquote_103 []
    blockquote_  = Blockquote_103 
instance C_Blockquote Ent105 Ent36 where
    _blockquote = Blockquote_105 []
    blockquote_  = Blockquote_105 
instance C_Blockquote Ent106 Ent36 where
    _blockquote = Blockquote_106 []
    blockquote_  = Blockquote_106 
instance C_Blockquote Ent109 Ent36 where
    _blockquote = Blockquote_109 []
    blockquote_  = Blockquote_109 
instance C_Blockquote Ent112 Ent11 where
    _blockquote = Blockquote_112 []
    blockquote_  = Blockquote_112 
instance C_Blockquote Ent114 Ent98 where
    _blockquote = Blockquote_114 []
    blockquote_  = Blockquote_114 
instance C_Blockquote Ent115 Ent98 where
    _blockquote = Blockquote_115 []
    blockquote_  = Blockquote_115 
instance C_Blockquote Ent117 Ent69 where
    _blockquote = Blockquote_117 []
    blockquote_  = Blockquote_117 
instance C_Blockquote Ent118 Ent69 where
    _blockquote = Blockquote_118 []
    blockquote_  = Blockquote_118 
instance C_Blockquote Ent121 Ent69 where
    _blockquote = Blockquote_121 []
    blockquote_  = Blockquote_121 
instance C_Blockquote Ent124 Ent98 where
    _blockquote = Blockquote_124 []
    blockquote_  = Blockquote_124 
instance C_Blockquote Ent128 Ent98 where
    _blockquote = Blockquote_128 []
    blockquote_  = Blockquote_128 
instance C_Blockquote Ent133 Ent93 where
    _blockquote = Blockquote_133 []
    blockquote_  = Blockquote_133 

class C_Ins a b | a -> b where
    _ins :: [b] -> a
    ins_ :: [Att14] -> [b] -> a
instance C_Ins Ent3 Ent94 where
    _ins = Ins_3 []
    ins_  = Ins_3 
instance C_Ins Ent4 Ent6 where
    _ins = Ins_4 []
    ins_  = Ins_4 
instance C_Ins Ent6 Ent6 where
    _ins = Ins_6 []
    ins_  = Ins_6 
instance C_Ins Ent7 Ent6 where
    _ins = Ins_7 []
    ins_  = Ins_7 
instance C_Ins Ent10 Ent6 where
    _ins = Ins_10 []
    ins_  = Ins_10 
instance C_Ins Ent11 Ent12 where
    _ins = Ins_11 []
    ins_  = Ins_11 
instance C_Ins Ent12 Ent12 where
    _ins = Ins_12 []
    ins_  = Ins_12 
instance C_Ins Ent13 Ent12 where
    _ins = Ins_13 []
    ins_  = Ins_13 
instance C_Ins Ent16 Ent12 where
    _ins = Ins_16 []
    ins_  = Ins_16 
instance C_Ins Ent17 Ent12 where
    _ins = Ins_17 []
    ins_  = Ins_17 
instance C_Ins Ent22 Ent6 where
    _ins = Ins_22 []
    ins_  = Ins_22 
instance C_Ins Ent27 Ent6 where
    _ins = Ins_27 []
    ins_  = Ins_27 
instance C_Ins Ent28 Ent6 where
    _ins = Ins_28 []
    ins_  = Ins_28 
instance C_Ins Ent29 Ent31 where
    _ins = Ins_29 []
    ins_  = Ins_29 
instance C_Ins Ent31 Ent31 where
    _ins = Ins_31 []
    ins_  = Ins_31 
instance C_Ins Ent32 Ent31 where
    _ins = Ins_32 []
    ins_  = Ins_32 
instance C_Ins Ent35 Ent31 where
    _ins = Ins_35 []
    ins_  = Ins_35 
instance C_Ins Ent36 Ent37 where
    _ins = Ins_36 []
    ins_  = Ins_36 
instance C_Ins Ent37 Ent37 where
    _ins = Ins_37 []
    ins_  = Ins_37 
instance C_Ins Ent38 Ent37 where
    _ins = Ins_38 []
    ins_  = Ins_38 
instance C_Ins Ent41 Ent37 where
    _ins = Ins_41 []
    ins_  = Ins_41 
instance C_Ins Ent42 Ent37 where
    _ins = Ins_42 []
    ins_  = Ins_42 
instance C_Ins Ent47 Ent31 where
    _ins = Ins_47 []
    ins_  = Ins_47 
instance C_Ins Ent52 Ent31 where
    _ins = Ins_52 []
    ins_  = Ins_52 
instance C_Ins Ent53 Ent31 where
    _ins = Ins_53 []
    ins_  = Ins_53 
instance C_Ins Ent56 Ent31 where
    _ins = Ins_56 []
    ins_  = Ins_56 
instance C_Ins Ent59 Ent6 where
    _ins = Ins_59 []
    ins_  = Ins_59 
instance C_Ins Ent60 Ent94 where
    _ins = Ins_60 []
    ins_  = Ins_60 
instance C_Ins Ent61 Ent94 where
    _ins = Ins_61 []
    ins_  = Ins_61 
instance C_Ins Ent62 Ent64 where
    _ins = Ins_62 []
    ins_  = Ins_62 
instance C_Ins Ent64 Ent64 where
    _ins = Ins_64 []
    ins_  = Ins_64 
instance C_Ins Ent65 Ent64 where
    _ins = Ins_65 []
    ins_  = Ins_65 
instance C_Ins Ent68 Ent64 where
    _ins = Ins_68 []
    ins_  = Ins_68 
instance C_Ins Ent69 Ent70 where
    _ins = Ins_69 []
    ins_  = Ins_69 
instance C_Ins Ent70 Ent70 where
    _ins = Ins_70 []
    ins_  = Ins_70 
instance C_Ins Ent71 Ent70 where
    _ins = Ins_71 []
    ins_  = Ins_71 
instance C_Ins Ent74 Ent70 where
    _ins = Ins_74 []
    ins_  = Ins_74 
instance C_Ins Ent75 Ent70 where
    _ins = Ins_75 []
    ins_  = Ins_75 
instance C_Ins Ent80 Ent64 where
    _ins = Ins_80 []
    ins_  = Ins_80 
instance C_Ins Ent85 Ent64 where
    _ins = Ins_85 []
    ins_  = Ins_85 
instance C_Ins Ent86 Ent64 where
    _ins = Ins_86 []
    ins_  = Ins_86 
instance C_Ins Ent89 Ent64 where
    _ins = Ins_89 []
    ins_  = Ins_89 
instance C_Ins Ent92 Ent94 where
    _ins = Ins_92 []
    ins_  = Ins_92 
instance C_Ins Ent93 Ent94 where
    _ins = Ins_93 []
    ins_  = Ins_93 
instance C_Ins Ent94 Ent94 where
    _ins = Ins_94 []
    ins_  = Ins_94 
instance C_Ins Ent97 Ent94 where
    _ins = Ins_97 []
    ins_  = Ins_97 
instance C_Ins Ent98 Ent100 where
    _ins = Ins_98 []
    ins_  = Ins_98 
instance C_Ins Ent100 Ent100 where
    _ins = Ins_100 []
    ins_  = Ins_100 
instance C_Ins Ent102 Ent12 where
    _ins = Ins_102 []
    ins_  = Ins_102 
instance C_Ins Ent103 Ent12 where
    _ins = Ins_103 []
    ins_  = Ins_103 
instance C_Ins Ent105 Ent37 where
    _ins = Ins_105 []
    ins_  = Ins_105 
instance C_Ins Ent106 Ent37 where
    _ins = Ins_106 []
    ins_  = Ins_106 
instance C_Ins Ent109 Ent37 where
    _ins = Ins_109 []
    ins_  = Ins_109 
instance C_Ins Ent112 Ent12 where
    _ins = Ins_112 []
    ins_  = Ins_112 
instance C_Ins Ent113 Ent100 where
    _ins = Ins_113 []
    ins_  = Ins_113 
instance C_Ins Ent114 Ent100 where
    _ins = Ins_114 []
    ins_  = Ins_114 
instance C_Ins Ent115 Ent100 where
    _ins = Ins_115 []
    ins_  = Ins_115 
instance C_Ins Ent117 Ent70 where
    _ins = Ins_117 []
    ins_  = Ins_117 
instance C_Ins Ent118 Ent70 where
    _ins = Ins_118 []
    ins_  = Ins_118 
instance C_Ins Ent121 Ent70 where
    _ins = Ins_121 []
    ins_  = Ins_121 
instance C_Ins Ent124 Ent100 where
    _ins = Ins_124 []
    ins_  = Ins_124 
instance C_Ins Ent127 Ent100 where
    _ins = Ins_127 []
    ins_  = Ins_127 
instance C_Ins Ent128 Ent100 where
    _ins = Ins_128 []
    ins_  = Ins_128 
instance C_Ins Ent133 Ent94 where
    _ins = Ins_133 []
    ins_  = Ins_133 

class C_Del a b | a -> b where
    _del :: [b] -> a
    del_ :: [Att14] -> [b] -> a
instance C_Del Ent3 Ent94 where
    _del = Del_3 []
    del_  = Del_3 
instance C_Del Ent4 Ent6 where
    _del = Del_4 []
    del_  = Del_4 
instance C_Del Ent6 Ent6 where
    _del = Del_6 []
    del_  = Del_6 
instance C_Del Ent7 Ent6 where
    _del = Del_7 []
    del_  = Del_7 
instance C_Del Ent10 Ent6 where
    _del = Del_10 []
    del_  = Del_10 
instance C_Del Ent11 Ent12 where
    _del = Del_11 []
    del_  = Del_11 
instance C_Del Ent12 Ent12 where
    _del = Del_12 []
    del_  = Del_12 
instance C_Del Ent13 Ent12 where
    _del = Del_13 []
    del_  = Del_13 
instance C_Del Ent16 Ent12 where
    _del = Del_16 []
    del_  = Del_16 
instance C_Del Ent17 Ent12 where
    _del = Del_17 []
    del_  = Del_17 
instance C_Del Ent22 Ent6 where
    _del = Del_22 []
    del_  = Del_22 
instance C_Del Ent27 Ent6 where
    _del = Del_27 []
    del_  = Del_27 
instance C_Del Ent28 Ent6 where
    _del = Del_28 []
    del_  = Del_28 
instance C_Del Ent29 Ent31 where
    _del = Del_29 []
    del_  = Del_29 
instance C_Del Ent31 Ent31 where
    _del = Del_31 []
    del_  = Del_31 
instance C_Del Ent32 Ent31 where
    _del = Del_32 []
    del_  = Del_32 
instance C_Del Ent35 Ent31 where
    _del = Del_35 []
    del_  = Del_35 
instance C_Del Ent36 Ent37 where
    _del = Del_36 []
    del_  = Del_36 
instance C_Del Ent37 Ent37 where
    _del = Del_37 []
    del_  = Del_37 
instance C_Del Ent38 Ent37 where
    _del = Del_38 []
    del_  = Del_38 
instance C_Del Ent41 Ent37 where
    _del = Del_41 []
    del_  = Del_41 
instance C_Del Ent42 Ent37 where
    _del = Del_42 []
    del_  = Del_42 
instance C_Del Ent47 Ent31 where
    _del = Del_47 []
    del_  = Del_47 
instance C_Del Ent52 Ent31 where
    _del = Del_52 []
    del_  = Del_52 
instance C_Del Ent53 Ent31 where
    _del = Del_53 []
    del_  = Del_53 
instance C_Del Ent56 Ent31 where
    _del = Del_56 []
    del_  = Del_56 
instance C_Del Ent59 Ent6 where
    _del = Del_59 []
    del_  = Del_59 
instance C_Del Ent60 Ent94 where
    _del = Del_60 []
    del_  = Del_60 
instance C_Del Ent61 Ent94 where
    _del = Del_61 []
    del_  = Del_61 
instance C_Del Ent62 Ent64 where
    _del = Del_62 []
    del_  = Del_62 
instance C_Del Ent64 Ent64 where
    _del = Del_64 []
    del_  = Del_64 
instance C_Del Ent65 Ent64 where
    _del = Del_65 []
    del_  = Del_65 
instance C_Del Ent68 Ent64 where
    _del = Del_68 []
    del_  = Del_68 
instance C_Del Ent69 Ent70 where
    _del = Del_69 []
    del_  = Del_69 
instance C_Del Ent70 Ent70 where
    _del = Del_70 []
    del_  = Del_70 
instance C_Del Ent71 Ent70 where
    _del = Del_71 []
    del_  = Del_71 
instance C_Del Ent74 Ent70 where
    _del = Del_74 []
    del_  = Del_74 
instance C_Del Ent75 Ent70 where
    _del = Del_75 []
    del_  = Del_75 
instance C_Del Ent80 Ent64 where
    _del = Del_80 []
    del_  = Del_80 
instance C_Del Ent85 Ent64 where
    _del = Del_85 []
    del_  = Del_85 
instance C_Del Ent86 Ent64 where
    _del = Del_86 []
    del_  = Del_86 
instance C_Del Ent89 Ent64 where
    _del = Del_89 []
    del_  = Del_89 
instance C_Del Ent92 Ent94 where
    _del = Del_92 []
    del_  = Del_92 
instance C_Del Ent93 Ent94 where
    _del = Del_93 []
    del_  = Del_93 
instance C_Del Ent94 Ent94 where
    _del = Del_94 []
    del_  = Del_94 
instance C_Del Ent97 Ent94 where
    _del = Del_97 []
    del_  = Del_97 
instance C_Del Ent98 Ent100 where
    _del = Del_98 []
    del_  = Del_98 
instance C_Del Ent100 Ent100 where
    _del = Del_100 []
    del_  = Del_100 
instance C_Del Ent102 Ent12 where
    _del = Del_102 []
    del_  = Del_102 
instance C_Del Ent103 Ent12 where
    _del = Del_103 []
    del_  = Del_103 
instance C_Del Ent105 Ent37 where
    _del = Del_105 []
    del_  = Del_105 
instance C_Del Ent106 Ent37 where
    _del = Del_106 []
    del_  = Del_106 
instance C_Del Ent109 Ent37 where
    _del = Del_109 []
    del_  = Del_109 
instance C_Del Ent112 Ent12 where
    _del = Del_112 []
    del_  = Del_112 
instance C_Del Ent113 Ent100 where
    _del = Del_113 []
    del_  = Del_113 
instance C_Del Ent114 Ent100 where
    _del = Del_114 []
    del_  = Del_114 
instance C_Del Ent115 Ent100 where
    _del = Del_115 []
    del_  = Del_115 
instance C_Del Ent117 Ent70 where
    _del = Del_117 []
    del_  = Del_117 
instance C_Del Ent118 Ent70 where
    _del = Del_118 []
    del_  = Del_118 
instance C_Del Ent121 Ent70 where
    _del = Del_121 []
    del_  = Del_121 
instance C_Del Ent124 Ent100 where
    _del = Del_124 []
    del_  = Del_124 
instance C_Del Ent127 Ent100 where
    _del = Del_127 []
    del_  = Del_127 
instance C_Del Ent128 Ent100 where
    _del = Del_128 []
    del_  = Del_128 
instance C_Del Ent133 Ent94 where
    _del = Del_133 []
    del_  = Del_133 

class C_A a b | a -> b where
    _a :: [b] -> a
    a_ :: [Att15] -> [b] -> a
instance C_A Ent3 Ent4 where
    _a = A_3 []
    a_  = A_3 
instance C_A Ent60 Ent4 where
    _a = A_60 []
    a_  = A_60 
instance C_A Ent62 Ent29 where
    _a = A_62 []
    a_  = A_62 
instance C_A Ent64 Ent29 where
    _a = A_64 []
    a_  = A_64 
instance C_A Ent68 Ent29 where
    _a = A_68 []
    a_  = A_68 
instance C_A Ent70 Ent38 where
    _a = A_70 []
    a_  = A_70 
instance C_A Ent71 Ent38 where
    _a = A_71 []
    a_  = A_71 
instance C_A Ent74 Ent38 where
    _a = A_74 []
    a_  = A_74 
instance C_A Ent75 Ent38 where
    _a = A_75 []
    a_  = A_75 
instance C_A Ent80 Ent29 where
    _a = A_80 []
    a_  = A_80 
instance C_A Ent85 Ent29 where
    _a = A_85 []
    a_  = A_85 
instance C_A Ent94 Ent4 where
    _a = A_94 []
    a_  = A_94 
instance C_A Ent97 Ent4 where
    _a = A_97 []
    a_  = A_97 
instance C_A Ent100 Ent13 where
    _a = A_100 []
    a_  = A_100 
instance C_A Ent113 Ent13 where
    _a = A_113 []
    a_  = A_113 
instance C_A Ent114 Ent13 where
    _a = A_114 []
    a_  = A_114 
instance C_A Ent117 Ent38 where
    _a = A_117 []
    a_  = A_117 
instance C_A Ent127 Ent13 where
    _a = A_127 []
    a_  = A_127 
instance C_A Ent128 Ent13 where
    _a = A_128 []
    a_  = A_128 
instance C_A Ent133 Ent4 where
    _a = A_133 []
    a_  = A_133 

class C_Span a b | a -> b where
    _span :: [b] -> a
    span_ :: [Att11] -> [b] -> a
instance C_Span Ent3 Ent60 where
    _span = Span_3 []
    span_  = Span_3 
instance C_Span Ent4 Ent4 where
    _span = Span_4 []
    span_  = Span_4 
instance C_Span Ent6 Ent4 where
    _span = Span_6 []
    span_  = Span_6 
instance C_Span Ent10 Ent4 where
    _span = Span_10 []
    span_  = Span_10 
instance C_Span Ent12 Ent13 where
    _span = Span_12 []
    span_  = Span_12 
instance C_Span Ent13 Ent13 where
    _span = Span_13 []
    span_  = Span_13 
instance C_Span Ent16 Ent13 where
    _span = Span_16 []
    span_  = Span_16 
instance C_Span Ent17 Ent13 where
    _span = Span_17 []
    span_  = Span_17 
instance C_Span Ent22 Ent4 where
    _span = Span_22 []
    span_  = Span_22 
instance C_Span Ent27 Ent4 where
    _span = Span_27 []
    span_  = Span_27 
instance C_Span Ent29 Ent29 where
    _span = Span_29 []
    span_  = Span_29 
instance C_Span Ent31 Ent29 where
    _span = Span_31 []
    span_  = Span_31 
instance C_Span Ent35 Ent29 where
    _span = Span_35 []
    span_  = Span_35 
instance C_Span Ent37 Ent38 where
    _span = Span_37 []
    span_  = Span_37 
instance C_Span Ent38 Ent38 where
    _span = Span_38 []
    span_  = Span_38 
instance C_Span Ent41 Ent38 where
    _span = Span_41 []
    span_  = Span_41 
instance C_Span Ent42 Ent38 where
    _span = Span_42 []
    span_  = Span_42 
instance C_Span Ent47 Ent29 where
    _span = Span_47 []
    span_  = Span_47 
instance C_Span Ent52 Ent29 where
    _span = Span_52 []
    span_  = Span_52 
instance C_Span Ent56 Ent29 where
    _span = Span_56 []
    span_  = Span_56 
instance C_Span Ent59 Ent4 where
    _span = Span_59 []
    span_  = Span_59 
instance C_Span Ent60 Ent60 where
    _span = Span_60 []
    span_  = Span_60 
instance C_Span Ent62 Ent62 where
    _span = Span_62 []
    span_  = Span_62 
instance C_Span Ent64 Ent62 where
    _span = Span_64 []
    span_  = Span_64 
instance C_Span Ent68 Ent62 where
    _span = Span_68 []
    span_  = Span_68 
instance C_Span Ent70 Ent71 where
    _span = Span_70 []
    span_  = Span_70 
instance C_Span Ent71 Ent71 where
    _span = Span_71 []
    span_  = Span_71 
instance C_Span Ent74 Ent71 where
    _span = Span_74 []
    span_  = Span_74 
instance C_Span Ent75 Ent71 where
    _span = Span_75 []
    span_  = Span_75 
instance C_Span Ent80 Ent62 where
    _span = Span_80 []
    span_  = Span_80 
instance C_Span Ent85 Ent62 where
    _span = Span_85 []
    span_  = Span_85 
instance C_Span Ent89 Ent62 where
    _span = Span_89 []
    span_  = Span_89 
instance C_Span Ent92 Ent60 where
    _span = Span_92 []
    span_  = Span_92 
instance C_Span Ent94 Ent60 where
    _span = Span_94 []
    span_  = Span_94 
instance C_Span Ent97 Ent60 where
    _span = Span_97 []
    span_  = Span_97 
instance C_Span Ent100 Ent113 where
    _span = Span_100 []
    span_  = Span_100 
instance C_Span Ent102 Ent13 where
    _span = Span_102 []
    span_  = Span_102 
instance C_Span Ent105 Ent38 where
    _span = Span_105 []
    span_  = Span_105 
instance C_Span Ent109 Ent38 where
    _span = Span_109 []
    span_  = Span_109 
instance C_Span Ent112 Ent13 where
    _span = Span_112 []
    span_  = Span_112 
instance C_Span Ent113 Ent113 where
    _span = Span_113 []
    span_  = Span_113 
instance C_Span Ent114 Ent113 where
    _span = Span_114 []
    span_  = Span_114 
instance C_Span Ent117 Ent71 where
    _span = Span_117 []
    span_  = Span_117 
instance C_Span Ent121 Ent71 where
    _span = Span_121 []
    span_  = Span_121 
instance C_Span Ent124 Ent113 where
    _span = Span_124 []
    span_  = Span_124 
instance C_Span Ent127 Ent113 where
    _span = Span_127 []
    span_  = Span_127 
instance C_Span Ent128 Ent113 where
    _span = Span_128 []
    span_  = Span_128 
instance C_Span Ent133 Ent60 where
    _span = Span_133 []
    span_  = Span_133 

class C_Bdo a b | a -> b where
    _bdo :: [b] -> a
    bdo_ :: [Att11] -> [b] -> a
instance C_Bdo Ent3 Ent60 where
    _bdo = Bdo_3 []
    bdo_  = Bdo_3 
instance C_Bdo Ent4 Ent4 where
    _bdo = Bdo_4 []
    bdo_  = Bdo_4 
instance C_Bdo Ent6 Ent4 where
    _bdo = Bdo_6 []
    bdo_  = Bdo_6 
instance C_Bdo Ent10 Ent4 where
    _bdo = Bdo_10 []
    bdo_  = Bdo_10 
instance C_Bdo Ent12 Ent13 where
    _bdo = Bdo_12 []
    bdo_  = Bdo_12 
instance C_Bdo Ent13 Ent13 where
    _bdo = Bdo_13 []
    bdo_  = Bdo_13 
instance C_Bdo Ent16 Ent13 where
    _bdo = Bdo_16 []
    bdo_  = Bdo_16 
instance C_Bdo Ent17 Ent13 where
    _bdo = Bdo_17 []
    bdo_  = Bdo_17 
instance C_Bdo Ent22 Ent4 where
    _bdo = Bdo_22 []
    bdo_  = Bdo_22 
instance C_Bdo Ent27 Ent4 where
    _bdo = Bdo_27 []
    bdo_  = Bdo_27 
instance C_Bdo Ent29 Ent29 where
    _bdo = Bdo_29 []
    bdo_  = Bdo_29 
instance C_Bdo Ent31 Ent29 where
    _bdo = Bdo_31 []
    bdo_  = Bdo_31 
instance C_Bdo Ent35 Ent29 where
    _bdo = Bdo_35 []
    bdo_  = Bdo_35 
instance C_Bdo Ent37 Ent38 where
    _bdo = Bdo_37 []
    bdo_  = Bdo_37 
instance C_Bdo Ent38 Ent38 where
    _bdo = Bdo_38 []
    bdo_  = Bdo_38 
instance C_Bdo Ent41 Ent38 where
    _bdo = Bdo_41 []
    bdo_  = Bdo_41 
instance C_Bdo Ent42 Ent38 where
    _bdo = Bdo_42 []
    bdo_  = Bdo_42 
instance C_Bdo Ent47 Ent29 where
    _bdo = Bdo_47 []
    bdo_  = Bdo_47 
instance C_Bdo Ent52 Ent29 where
    _bdo = Bdo_52 []
    bdo_  = Bdo_52 
instance C_Bdo Ent56 Ent29 where
    _bdo = Bdo_56 []
    bdo_  = Bdo_56 
instance C_Bdo Ent59 Ent4 where
    _bdo = Bdo_59 []
    bdo_  = Bdo_59 
instance C_Bdo Ent60 Ent60 where
    _bdo = Bdo_60 []
    bdo_  = Bdo_60 
instance C_Bdo Ent62 Ent62 where
    _bdo = Bdo_62 []
    bdo_  = Bdo_62 
instance C_Bdo Ent64 Ent62 where
    _bdo = Bdo_64 []
    bdo_  = Bdo_64 
instance C_Bdo Ent68 Ent62 where
    _bdo = Bdo_68 []
    bdo_  = Bdo_68 
instance C_Bdo Ent70 Ent71 where
    _bdo = Bdo_70 []
    bdo_  = Bdo_70 
instance C_Bdo Ent71 Ent71 where
    _bdo = Bdo_71 []
    bdo_  = Bdo_71 
instance C_Bdo Ent74 Ent71 where
    _bdo = Bdo_74 []
    bdo_  = Bdo_74 
instance C_Bdo Ent75 Ent71 where
    _bdo = Bdo_75 []
    bdo_  = Bdo_75 
instance C_Bdo Ent80 Ent62 where
    _bdo = Bdo_80 []
    bdo_  = Bdo_80 
instance C_Bdo Ent85 Ent62 where
    _bdo = Bdo_85 []
    bdo_  = Bdo_85 
instance C_Bdo Ent89 Ent62 where
    _bdo = Bdo_89 []
    bdo_  = Bdo_89 
instance C_Bdo Ent92 Ent60 where
    _bdo = Bdo_92 []
    bdo_  = Bdo_92 
instance C_Bdo Ent94 Ent60 where
    _bdo = Bdo_94 []
    bdo_  = Bdo_94 
instance C_Bdo Ent97 Ent60 where
    _bdo = Bdo_97 []
    bdo_  = Bdo_97 
instance C_Bdo Ent100 Ent113 where
    _bdo = Bdo_100 []
    bdo_  = Bdo_100 
instance C_Bdo Ent102 Ent13 where
    _bdo = Bdo_102 []
    bdo_  = Bdo_102 
instance C_Bdo Ent105 Ent38 where
    _bdo = Bdo_105 []
    bdo_  = Bdo_105 
instance C_Bdo Ent109 Ent38 where
    _bdo = Bdo_109 []
    bdo_  = Bdo_109 
instance C_Bdo Ent112 Ent13 where
    _bdo = Bdo_112 []
    bdo_  = Bdo_112 
instance C_Bdo Ent113 Ent113 where
    _bdo = Bdo_113 []
    bdo_  = Bdo_113 
instance C_Bdo Ent114 Ent113 where
    _bdo = Bdo_114 []
    bdo_  = Bdo_114 
instance C_Bdo Ent117 Ent71 where
    _bdo = Bdo_117 []
    bdo_  = Bdo_117 
instance C_Bdo Ent121 Ent71 where
    _bdo = Bdo_121 []
    bdo_  = Bdo_121 
instance C_Bdo Ent124 Ent113 where
    _bdo = Bdo_124 []
    bdo_  = Bdo_124 
instance C_Bdo Ent127 Ent113 where
    _bdo = Bdo_127 []
    bdo_  = Bdo_127 
instance C_Bdo Ent128 Ent113 where
    _bdo = Bdo_128 []
    bdo_  = Bdo_128 
instance C_Bdo Ent133 Ent60 where
    _bdo = Bdo_133 []
    bdo_  = Bdo_133 

class C_Br a where
    _br :: a
    br_ :: [Att18] -> a
instance C_Br Ent3 where
    _br = Br_3 []
    br_ = Br_3 
instance C_Br Ent4 where
    _br = Br_4 []
    br_ = Br_4 
instance C_Br Ent6 where
    _br = Br_6 []
    br_ = Br_6 
instance C_Br Ent10 where
    _br = Br_10 []
    br_ = Br_10 
instance C_Br Ent12 where
    _br = Br_12 []
    br_ = Br_12 
instance C_Br Ent13 where
    _br = Br_13 []
    br_ = Br_13 
instance C_Br Ent16 where
    _br = Br_16 []
    br_ = Br_16 
instance C_Br Ent17 where
    _br = Br_17 []
    br_ = Br_17 
instance C_Br Ent22 where
    _br = Br_22 []
    br_ = Br_22 
instance C_Br Ent27 where
    _br = Br_27 []
    br_ = Br_27 
instance C_Br Ent29 where
    _br = Br_29 []
    br_ = Br_29 
instance C_Br Ent31 where
    _br = Br_31 []
    br_ = Br_31 
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 Ent41 where
    _br = Br_41 []
    br_ = Br_41 
instance C_Br Ent42 where
    _br = Br_42 []
    br_ = Br_42 
instance C_Br Ent47 where
    _br = Br_47 []
    br_ = Br_47 
instance C_Br Ent52 where
    _br = Br_52 []
    br_ = Br_52 
instance C_Br Ent56 where
    _br = Br_56 []
    br_ = Br_56 
instance C_Br Ent59 where
    _br = Br_59 []
    br_ = Br_59 
instance C_Br Ent60 where
    _br = Br_60 []
    br_ = Br_60 
instance C_Br Ent62 where
    _br = Br_62 []
    br_ = Br_62 
instance C_Br Ent64 where
    _br = Br_64 []
    br_ = Br_64 
instance C_Br Ent68 where
    _br = Br_68 []
    br_ = Br_68 
instance C_Br Ent70 where
    _br = Br_70 []
    br_ = Br_70 
instance C_Br Ent71 where
    _br = Br_71 []
    br_ = Br_71 
instance C_Br Ent74 where
    _br = Br_74 []
    br_ = Br_74 
instance C_Br Ent75 where
    _br = Br_75 []
    br_ = Br_75 
instance C_Br Ent80 where
    _br = Br_80 []
    br_ = Br_80 
instance C_Br Ent85 where
    _br = Br_85 []
    br_ = Br_85 
instance C_Br Ent89 where
    _br = Br_89 []
    br_ = Br_89 
instance C_Br Ent92 where
    _br = Br_92 []
    br_ = Br_92 
instance C_Br Ent94 where
    _br = Br_94 []
    br_ = Br_94 
instance C_Br Ent97 where
    _br = Br_97 []
    br_ = Br_97 
instance C_Br Ent100 where
    _br = Br_100 []
    br_ = Br_100 
instance C_Br Ent102 where
    _br = Br_102 []
    br_ = Br_102 
instance C_Br Ent105 where
    _br = Br_105 []
    br_ = Br_105 
instance C_Br Ent109 where
    _br = Br_109 []
    br_ = Br_109 
instance C_Br Ent112 where
    _br = Br_112 []
    br_ = Br_112 
instance C_Br Ent113 where
    _br = Br_113 []
    br_ = Br_113 
instance C_Br Ent114 where
    _br = Br_114 []
    br_ = Br_114 
instance C_Br Ent117 where
    _br = Br_117 []
    br_ = Br_117 
instance C_Br Ent121 where
    _br = Br_121 []
    br_ = Br_121 
instance C_Br Ent124 where
    _br = Br_124 []
    br_ = Br_124 
instance C_Br Ent127 where
    _br = Br_127 []
    br_ = Br_127 
instance C_Br Ent128 where
    _br = Br_128 []
    br_ = Br_128 
instance C_Br Ent133 where
    _br = Br_133 []
    br_ = Br_133 

class C_Em a b | a -> b where
    _em :: [b] -> a
    em_ :: [Att11] -> [b] -> a
instance C_Em Ent3 Ent60 where
    _em = Em_3 []
    em_  = Em_3 
instance C_Em Ent4 Ent4 where
    _em = Em_4 []
    em_  = Em_4 
instance C_Em Ent6 Ent4 where
    _em = Em_6 []
    em_  = Em_6 
instance C_Em Ent10 Ent4 where
    _em = Em_10 []
    em_  = Em_10 
instance C_Em Ent12 Ent13 where
    _em = Em_12 []
    em_  = Em_12 
instance C_Em Ent13 Ent13 where
    _em = Em_13 []
    em_  = Em_13 
instance C_Em Ent16 Ent13 where
    _em = Em_16 []
    em_  = Em_16 
instance C_Em Ent17 Ent13 where
    _em = Em_17 []
    em_  = Em_17 
instance C_Em Ent22 Ent4 where
    _em = Em_22 []
    em_  = Em_22 
instance C_Em Ent27 Ent4 where
    _em = Em_27 []
    em_  = Em_27 
instance C_Em Ent29 Ent29 where
    _em = Em_29 []
    em_  = Em_29 
instance C_Em Ent31 Ent29 where
    _em = Em_31 []
    em_  = Em_31 
instance C_Em Ent35 Ent29 where
    _em = Em_35 []
    em_  = Em_35 
instance C_Em Ent37 Ent38 where
    _em = Em_37 []
    em_  = Em_37 
instance C_Em Ent38 Ent38 where
    _em = Em_38 []
    em_  = Em_38 
instance C_Em Ent41 Ent38 where
    _em = Em_41 []
    em_  = Em_41 
instance C_Em Ent42 Ent38 where
    _em = Em_42 []
    em_  = Em_42 
instance C_Em Ent47 Ent29 where
    _em = Em_47 []
    em_  = Em_47 
instance C_Em Ent52 Ent29 where
    _em = Em_52 []
    em_  = Em_52 
instance C_Em Ent56 Ent29 where
    _em = Em_56 []
    em_  = Em_56 
instance C_Em Ent59 Ent4 where
    _em = Em_59 []
    em_  = Em_59 
instance C_Em Ent60 Ent60 where
    _em = Em_60 []
    em_  = Em_60 
instance C_Em Ent62 Ent62 where
    _em = Em_62 []
    em_  = Em_62 
instance C_Em Ent64 Ent62 where
    _em = Em_64 []
    em_  = Em_64 
instance C_Em Ent68 Ent62 where
    _em = Em_68 []
    em_  = Em_68 
instance C_Em Ent70 Ent71 where
    _em = Em_70 []
    em_  = Em_70 
instance C_Em Ent71 Ent71 where
    _em = Em_71 []
    em_  = Em_71 
instance C_Em Ent74 Ent71 where
    _em = Em_74 []
    em_  = Em_74 
instance C_Em Ent75 Ent71 where
    _em = Em_75 []
    em_  = Em_75 
instance C_Em Ent80 Ent62 where
    _em = Em_80 []
    em_  = Em_80 
instance C_Em Ent85 Ent62 where
    _em = Em_85 []
    em_  = Em_85 
instance C_Em Ent89 Ent62 where
    _em = Em_89 []
    em_  = Em_89 
instance C_Em Ent92 Ent60 where
    _em = Em_92 []
    em_  = Em_92 
instance C_Em Ent94 Ent60 where
    _em = Em_94 []
    em_  = Em_94 
instance C_Em Ent97 Ent60 where
    _em = Em_97 []
    em_  = Em_97 
instance C_Em Ent100 Ent113 where
    _em = Em_100 []
    em_  = Em_100 
instance C_Em Ent102 Ent13 where
    _em = Em_102 []
    em_  = Em_102 
instance C_Em Ent105 Ent38 where
    _em = Em_105 []
    em_  = Em_105 
instance C_Em Ent109 Ent38 where
    _em = Em_109 []
    em_  = Em_109 
instance C_Em Ent112 Ent13 where
    _em = Em_112 []
    em_  = Em_112 
instance C_Em Ent113 Ent113 where
    _em = Em_113 []
    em_  = Em_113 
instance C_Em Ent114 Ent113 where
    _em = Em_114 []
    em_  = Em_114 
instance C_Em Ent117 Ent71 where
    _em = Em_117 []
    em_  = Em_117 
instance C_Em Ent121 Ent71 where
    _em = Em_121 []
    em_  = Em_121 
instance C_Em Ent124 Ent113 where
    _em = Em_124 []
    em_  = Em_124 
instance C_Em Ent127 Ent113 where
    _em = Em_127 []
    em_  = Em_127 
instance C_Em Ent128 Ent113 where
    _em = Em_128 []
    em_  = Em_128 
instance C_Em Ent133 Ent60 where
    _em = Em_133 []
    em_  = Em_133 

class C_Strong a b | a -> b where
    _strong :: [b] -> a
    strong_ :: [Att11] -> [b] -> a
instance C_Strong Ent3 Ent60 where
    _strong = Strong_3 []
    strong_  = Strong_3 
instance C_Strong Ent4 Ent4 where
    _strong = Strong_4 []
    strong_  = Strong_4 
instance C_Strong Ent6 Ent4 where
    _strong = Strong_6 []
    strong_  = Strong_6 
instance C_Strong Ent10 Ent4 where
    _strong = Strong_10 []
    strong_  = Strong_10 
instance C_Strong Ent12 Ent13 where
    _strong = Strong_12 []
    strong_  = Strong_12 
instance C_Strong Ent13 Ent13 where
    _strong = Strong_13 []
    strong_  = Strong_13 
instance C_Strong Ent16 Ent13 where
    _strong = Strong_16 []
    strong_  = Strong_16 
instance C_Strong Ent17 Ent13 where
    _strong = Strong_17 []
    strong_  = Strong_17 
instance C_Strong Ent22 Ent4 where
    _strong = Strong_22 []
    strong_  = Strong_22 
instance C_Strong Ent27 Ent4 where
    _strong = Strong_27 []
    strong_  = Strong_27 
instance C_Strong Ent29 Ent29 where
    _strong = Strong_29 []
    strong_  = Strong_29 
instance C_Strong Ent31 Ent29 where
    _strong = Strong_31 []
    strong_  = Strong_31 
instance C_Strong Ent35 Ent29 where
    _strong = Strong_35 []
    strong_  = Strong_35 
instance C_Strong Ent37 Ent38 where
    _strong = Strong_37 []
    strong_  = Strong_37 
instance C_Strong Ent38 Ent38 where
    _strong = Strong_38 []
    strong_  = Strong_38 
instance C_Strong Ent41 Ent38 where
    _strong = Strong_41 []
    strong_  = Strong_41 
instance C_Strong Ent42 Ent38 where
    _strong = Strong_42 []
    strong_  = Strong_42 
instance C_Strong Ent47 Ent29 where
    _strong = Strong_47 []
    strong_  = Strong_47 
instance C_Strong Ent52 Ent29 where
    _strong = Strong_52 []
    strong_  = Strong_52 
instance C_Strong Ent56 Ent29 where
    _strong = Strong_56 []
    strong_  = Strong_56 
instance C_Strong Ent59 Ent4 where
    _strong = Strong_59 []
    strong_  = Strong_59 
instance C_Strong Ent60 Ent60 where
    _strong = Strong_60 []
    strong_  = Strong_60 
instance C_Strong Ent62 Ent62 where
    _strong = Strong_62 []
    strong_  = Strong_62 
instance C_Strong Ent64 Ent62 where
    _strong = Strong_64 []
    strong_  = Strong_64 
instance C_Strong Ent68 Ent62 where
    _strong = Strong_68 []
    strong_  = Strong_68 
instance C_Strong Ent70 Ent71 where
    _strong = Strong_70 []
    strong_  = Strong_70 
instance C_Strong Ent71 Ent71 where
    _strong = Strong_71 []
    strong_  = Strong_71 
instance C_Strong Ent74 Ent71 where
    _strong = Strong_74 []
    strong_  = Strong_74 
instance C_Strong Ent75 Ent71 where
    _strong = Strong_75 []
    strong_  = Strong_75 
instance C_Strong Ent80 Ent62 where
    _strong = Strong_80 []
    strong_  = Strong_80 
instance C_Strong Ent85 Ent62 where
    _strong = Strong_85 []
    strong_  = Strong_85 
instance C_Strong Ent89 Ent62 where
    _strong = Strong_89 []
    strong_  = Strong_89 
instance C_Strong Ent92 Ent60 where
    _strong = Strong_92 []
    strong_  = Strong_92 
instance C_Strong Ent94 Ent60 where
    _strong = Strong_94 []
    strong_  = Strong_94 
instance C_Strong Ent97 Ent60 where
    _strong = Strong_97 []
    strong_  = Strong_97 
instance C_Strong Ent100 Ent113 where
    _strong = Strong_100 []
    strong_  = Strong_100 
instance C_Strong Ent102 Ent13 where
    _strong = Strong_102 []
    strong_  = Strong_102 
instance C_Strong Ent105 Ent38 where
    _strong = Strong_105 []
    strong_  = Strong_105 
instance C_Strong Ent109 Ent38 where
    _strong = Strong_109 []
    strong_  = Strong_109 
instance C_Strong Ent112 Ent13 where
    _strong = Strong_112 []
    strong_  = Strong_112 
instance C_Strong Ent113 Ent113 where
    _strong = Strong_113 []
    strong_  = Strong_113 
instance C_Strong Ent114 Ent113 where
    _strong = Strong_114 []
    strong_  = Strong_114 
instance C_Strong Ent117 Ent71 where
    _strong = Strong_117 []
    strong_  = Strong_117 
instance C_Strong Ent121 Ent71 where
    _strong = Strong_121 []
    strong_  = Strong_121 
instance C_Strong Ent124 Ent113 where
    _strong = Strong_124 []
    strong_  = Strong_124 
instance C_Strong Ent127 Ent113 where
    _strong = Strong_127 []
    strong_  = Strong_127 
instance C_Strong Ent128 Ent113 where
    _strong = Strong_128 []
    strong_  = Strong_128 
instance C_Strong Ent133 Ent60 where
    _strong = Strong_133 []
    strong_  = Strong_133 

class C_Dfn a b | a -> b where
    _dfn :: [b] -> a
    dfn_ :: [Att11] -> [b] -> a
instance C_Dfn Ent3 Ent60 where
    _dfn = Dfn_3 []
    dfn_  = Dfn_3 
instance C_Dfn Ent4 Ent4 where
    _dfn = Dfn_4 []
    dfn_  = Dfn_4 
instance C_Dfn Ent6 Ent4 where
    _dfn = Dfn_6 []
    dfn_  = Dfn_6 
instance C_Dfn Ent10 Ent4 where
    _dfn = Dfn_10 []
    dfn_  = Dfn_10 
instance C_Dfn Ent12 Ent13 where
    _dfn = Dfn_12 []
    dfn_  = Dfn_12 
instance C_Dfn Ent13 Ent13 where
    _dfn = Dfn_13 []
    dfn_  = Dfn_13 
instance C_Dfn Ent16 Ent13 where
    _dfn = Dfn_16 []
    dfn_  = Dfn_16 
instance C_Dfn Ent17 Ent13 where
    _dfn = Dfn_17 []
    dfn_  = Dfn_17 
instance C_Dfn Ent22 Ent4 where
    _dfn = Dfn_22 []
    dfn_  = Dfn_22 
instance C_Dfn Ent27 Ent4 where
    _dfn = Dfn_27 []
    dfn_  = Dfn_27 
instance C_Dfn Ent29 Ent29 where
    _dfn = Dfn_29 []
    dfn_  = Dfn_29 
instance C_Dfn Ent31 Ent29 where
    _dfn = Dfn_31 []
    dfn_  = Dfn_31 
instance C_Dfn Ent35 Ent29 where
    _dfn = Dfn_35 []
    dfn_  = Dfn_35 
instance C_Dfn Ent37 Ent38 where
    _dfn = Dfn_37 []
    dfn_  = Dfn_37 
instance C_Dfn Ent38 Ent38 where
    _dfn = Dfn_38 []
    dfn_  = Dfn_38 
instance C_Dfn Ent41 Ent38 where
    _dfn = Dfn_41 []
    dfn_  = Dfn_41 
instance C_Dfn Ent42 Ent38 where
    _dfn = Dfn_42 []
    dfn_  = Dfn_42 
instance C_Dfn Ent47 Ent29 where
    _dfn = Dfn_47 []
    dfn_  = Dfn_47 
instance C_Dfn Ent52 Ent29 where
    _dfn = Dfn_52 []
    dfn_  = Dfn_52 
instance C_Dfn Ent56 Ent29 where
    _dfn = Dfn_56 []
    dfn_  = Dfn_56 
instance C_Dfn Ent59 Ent4 where
    _dfn = Dfn_59 []
    dfn_  = Dfn_59 
instance C_Dfn Ent60 Ent60 where
    _dfn = Dfn_60 []
    dfn_  = Dfn_60 
instance C_Dfn Ent62 Ent62 where
    _dfn = Dfn_62 []
    dfn_  = Dfn_62 
instance C_Dfn Ent64 Ent62 where
    _dfn = Dfn_64 []
    dfn_  = Dfn_64 
instance C_Dfn Ent68 Ent62 where
    _dfn = Dfn_68 []
    dfn_  = Dfn_68 
instance C_Dfn Ent70 Ent71 where
    _dfn = Dfn_70 []
    dfn_  = Dfn_70 
instance C_Dfn Ent71 Ent71 where
    _dfn = Dfn_71 []
    dfn_  = Dfn_71 
instance C_Dfn Ent74 Ent71 where
    _dfn = Dfn_74 []
    dfn_  = Dfn_74 
instance C_Dfn Ent75 Ent71 where
    _dfn = Dfn_75 []
    dfn_  = Dfn_75 
instance C_Dfn Ent80 Ent62 where
    _dfn = Dfn_80 []
    dfn_  = Dfn_80 
instance C_Dfn Ent85 Ent62 where
    _dfn = Dfn_85 []
    dfn_  = Dfn_85 
instance C_Dfn Ent89 Ent62 where
    _dfn = Dfn_89 []
    dfn_  = Dfn_89 
instance C_Dfn Ent92 Ent60 where
    _dfn = Dfn_92 []
    dfn_  = Dfn_92 
instance C_Dfn Ent94 Ent60 where
    _dfn = Dfn_94 []
    dfn_  = Dfn_94 
instance C_Dfn Ent97 Ent60 where
    _dfn = Dfn_97 []
    dfn_  = Dfn_97 
instance C_Dfn Ent100 Ent113 where
    _dfn = Dfn_100 []
    dfn_  = Dfn_100 
instance C_Dfn Ent102 Ent13 where
    _dfn = Dfn_102 []
    dfn_  = Dfn_102 
instance C_Dfn Ent105 Ent38 where
    _dfn = Dfn_105 []
    dfn_  = Dfn_105 
instance C_Dfn Ent109 Ent38 where
    _dfn = Dfn_109 []
    dfn_  = Dfn_109 
instance C_Dfn Ent112 Ent13 where
    _dfn = Dfn_112 []
    dfn_  = Dfn_112 
instance C_Dfn Ent113 Ent113 where
    _dfn = Dfn_113 []
    dfn_  = Dfn_113 
instance C_Dfn Ent114 Ent113 where
    _dfn = Dfn_114 []
    dfn_  = Dfn_114 
instance C_Dfn Ent117 Ent71 where
    _dfn = Dfn_117 []
    dfn_  = Dfn_117 
instance C_Dfn Ent121 Ent71 where
    _dfn = Dfn_121 []
    dfn_  = Dfn_121 
instance C_Dfn Ent124 Ent113 where
    _dfn = Dfn_124 []
    dfn_  = Dfn_124 
instance C_Dfn Ent127 Ent113 where
    _dfn = Dfn_127 []
    dfn_  = Dfn_127 
instance C_Dfn Ent128 Ent113 where
    _dfn = Dfn_128 []
    dfn_  = Dfn_128 
instance C_Dfn Ent133 Ent60 where
    _dfn = Dfn_133 []
    dfn_  = Dfn_133 

class C_Code a b | a -> b where
    _code :: [b] -> a
    code_ :: [Att11] -> [b] -> a
instance C_Code Ent3 Ent60 where
    _code = Code_3 []
    code_  = Code_3 
instance C_Code Ent4 Ent4 where
    _code = Code_4 []
    code_  = Code_4 
instance C_Code Ent6 Ent4 where
    _code = Code_6 []
    code_  = Code_6 
instance C_Code Ent10 Ent4 where
    _code = Code_10 []
    code_  = Code_10 
instance C_Code Ent12 Ent13 where
    _code = Code_12 []
    code_  = Code_12 
instance C_Code Ent13 Ent13 where
    _code = Code_13 []
    code_  = Code_13 
instance C_Code Ent16 Ent13 where
    _code = Code_16 []
    code_  = Code_16 
instance C_Code Ent17 Ent13 where
    _code = Code_17 []
    code_  = Code_17 
instance C_Code Ent22 Ent4 where
    _code = Code_22 []
    code_  = Code_22 
instance C_Code Ent27 Ent4 where
    _code = Code_27 []
    code_  = Code_27 
instance C_Code Ent29 Ent29 where
    _code = Code_29 []
    code_  = Code_29 
instance C_Code Ent31 Ent29 where
    _code = Code_31 []
    code_  = Code_31 
instance C_Code Ent35 Ent29 where
    _code = Code_35 []
    code_  = Code_35 
instance C_Code Ent37 Ent38 where
    _code = Code_37 []
    code_  = Code_37 
instance C_Code Ent38 Ent38 where
    _code = Code_38 []
    code_  = Code_38 
instance C_Code Ent41 Ent38 where
    _code = Code_41 []
    code_  = Code_41 
instance C_Code Ent42 Ent38 where
    _code = Code_42 []
    code_  = Code_42 
instance C_Code Ent47 Ent29 where
    _code = Code_47 []
    code_  = Code_47 
instance C_Code Ent52 Ent29 where
    _code = Code_52 []
    code_  = Code_52 
instance C_Code Ent56 Ent29 where
    _code = Code_56 []
    code_  = Code_56 
instance C_Code Ent59 Ent4 where
    _code = Code_59 []
    code_  = Code_59 
instance C_Code Ent60 Ent60 where
    _code = Code_60 []
    code_  = Code_60 
instance C_Code Ent62 Ent62 where
    _code = Code_62 []
    code_  = Code_62 
instance C_Code Ent64 Ent62 where
    _code = Code_64 []
    code_  = Code_64 
instance C_Code Ent68 Ent62 where
    _code = Code_68 []
    code_  = Code_68 
instance C_Code Ent70 Ent71 where
    _code = Code_70 []
    code_  = Code_70 
instance C_Code Ent71 Ent71 where
    _code = Code_71 []
    code_  = Code_71 
instance C_Code Ent74 Ent71 where
    _code = Code_74 []
    code_  = Code_74 
instance C_Code Ent75 Ent71 where
    _code = Code_75 []
    code_  = Code_75 
instance C_Code Ent80 Ent62 where
    _code = Code_80 []
    code_  = Code_80 
instance C_Code Ent85 Ent62 where
    _code = Code_85 []
    code_  = Code_85 
instance C_Code Ent89 Ent62 where
    _code = Code_89 []
    code_  = Code_89 
instance C_Code Ent92 Ent60 where
    _code = Code_92 []
    code_  = Code_92 
instance C_Code Ent94 Ent60 where
    _code = Code_94 []
    code_  = Code_94 
instance C_Code Ent97 Ent60 where
    _code = Code_97 []
    code_  = Code_97 
instance C_Code Ent100 Ent113 where
    _code = Code_100 []
    code_  = Code_100 
instance C_Code Ent102 Ent13 where
    _code = Code_102 []
    code_  = Code_102 
instance C_Code Ent105 Ent38 where
    _code = Code_105 []
    code_  = Code_105 
instance C_Code Ent109 Ent38 where
    _code = Code_109 []
    code_  = Code_109 
instance C_Code Ent112 Ent13 where
    _code = Code_112 []
    code_  = Code_112 
instance C_Code Ent113 Ent113 where
    _code = Code_113 []
    code_  = Code_113 
instance C_Code Ent114 Ent113 where
    _code = Code_114 []
    code_  = Code_114 
instance C_Code Ent117 Ent71 where
    _code = Code_117 []
    code_  = Code_117 
instance C_Code Ent121 Ent71 where
    _code = Code_121 []
    code_  = Code_121 
instance C_Code Ent124 Ent113 where
    _code = Code_124 []
    code_  = Code_124 
instance C_Code Ent127 Ent113 where
    _code = Code_127 []
    code_  = Code_127 
instance C_Code Ent128 Ent113 where
    _code = Code_128 []
    code_  = Code_128 
instance C_Code Ent133 Ent60 where
    _code = Code_133 []
    code_  = Code_133 

class C_Samp a b | a -> b where
    _samp :: [b] -> a
    samp_ :: [Att11] -> [b] -> a
instance C_Samp Ent3 Ent60 where
    _samp = Samp_3 []
    samp_  = Samp_3 
instance C_Samp Ent4 Ent4 where
    _samp = Samp_4 []
    samp_  = Samp_4 
instance C_Samp Ent6 Ent4 where
    _samp = Samp_6 []
    samp_  = Samp_6 
instance C_Samp Ent10 Ent4 where
    _samp = Samp_10 []
    samp_  = Samp_10 
instance C_Samp Ent12 Ent13 where
    _samp = Samp_12 []
    samp_  = Samp_12 
instance C_Samp Ent13 Ent13 where
    _samp = Samp_13 []
    samp_  = Samp_13 
instance C_Samp Ent16 Ent13 where
    _samp = Samp_16 []
    samp_  = Samp_16 
instance C_Samp Ent17 Ent13 where
    _samp = Samp_17 []
    samp_  = Samp_17 
instance C_Samp Ent22 Ent4 where
    _samp = Samp_22 []
    samp_  = Samp_22 
instance C_Samp Ent27 Ent4 where
    _samp = Samp_27 []
    samp_  = Samp_27 
instance C_Samp Ent29 Ent29 where
    _samp = Samp_29 []
    samp_  = Samp_29 
instance C_Samp Ent31 Ent29 where
    _samp = Samp_31 []
    samp_  = Samp_31 
instance C_Samp Ent35 Ent29 where
    _samp = Samp_35 []
    samp_  = Samp_35 
instance C_Samp Ent37 Ent38 where
    _samp = Samp_37 []
    samp_  = Samp_37 
instance C_Samp Ent38 Ent38 where
    _samp = Samp_38 []
    samp_  = Samp_38 
instance C_Samp Ent41 Ent38 where
    _samp = Samp_41 []
    samp_  = Samp_41 
instance C_Samp Ent42 Ent38 where
    _samp = Samp_42 []
    samp_  = Samp_42 
instance C_Samp Ent47 Ent29 where
    _samp = Samp_47 []
    samp_  = Samp_47 
instance C_Samp Ent52 Ent29 where
    _samp = Samp_52 []
    samp_  = Samp_52 
instance C_Samp Ent56 Ent29 where
    _samp = Samp_56 []
    samp_  = Samp_56 
instance C_Samp Ent59 Ent4 where
    _samp = Samp_59 []
    samp_  = Samp_59 
instance C_Samp Ent60 Ent60 where
    _samp = Samp_60 []
    samp_  = Samp_60 
instance C_Samp Ent62 Ent62 where
    _samp = Samp_62 []
    samp_  = Samp_62 
instance C_Samp Ent64 Ent62 where
    _samp = Samp_64 []
    samp_  = Samp_64 
instance C_Samp Ent68 Ent62 where
    _samp = Samp_68 []
    samp_  = Samp_68 
instance C_Samp Ent70 Ent71 where
    _samp = Samp_70 []
    samp_  = Samp_70 
instance C_Samp Ent71 Ent71 where
    _samp = Samp_71 []
    samp_  = Samp_71 
instance C_Samp Ent74 Ent71 where
    _samp = Samp_74 []
    samp_  = Samp_74 
instance C_Samp Ent75 Ent71 where
    _samp = Samp_75 []
    samp_  = Samp_75 
instance C_Samp Ent80 Ent62 where
    _samp = Samp_80 []
    samp_  = Samp_80 
instance C_Samp Ent85 Ent62 where
    _samp = Samp_85 []
    samp_  = Samp_85 
instance C_Samp Ent89 Ent62 where
    _samp = Samp_89 []
    samp_  = Samp_89 
instance C_Samp Ent92 Ent60 where
    _samp = Samp_92 []
    samp_  = Samp_92 
instance C_Samp Ent94 Ent60 where
    _samp = Samp_94 []
    samp_  = Samp_94 
instance C_Samp Ent97 Ent60 where
    _samp = Samp_97 []
    samp_  = Samp_97 
instance C_Samp Ent100 Ent113 where
    _samp = Samp_100 []
    samp_  = Samp_100 
instance C_Samp Ent102 Ent13 where
    _samp = Samp_102 []
    samp_  = Samp_102 
instance C_Samp Ent105 Ent38 where
    _samp = Samp_105 []
    samp_  = Samp_105 
instance C_Samp Ent109 Ent38 where
    _samp = Samp_109 []
    samp_  = Samp_109 
instance C_Samp Ent112 Ent13 where
    _samp = Samp_112 []
    samp_  = Samp_112 
instance C_Samp Ent113 Ent113 where
    _samp = Samp_113 []
    samp_  = Samp_113 
instance C_Samp Ent114 Ent113 where
    _samp = Samp_114 []
    samp_  = Samp_114 
instance C_Samp Ent117 Ent71 where
    _samp = Samp_117 []
    samp_  = Samp_117 
instance C_Samp Ent121 Ent71 where
    _samp = Samp_121 []
    samp_  = Samp_121 
instance C_Samp Ent124 Ent113 where
    _samp = Samp_124 []
    samp_  = Samp_124 
instance C_Samp Ent127 Ent113 where
    _samp = Samp_127 []
    samp_  = Samp_127 
instance C_Samp Ent128 Ent113 where
    _samp = Samp_128 []
    samp_  = Samp_128 
instance C_Samp Ent133 Ent60 where
    _samp = Samp_133 []
    samp_  = Samp_133 

class C_Kbd a b | a -> b where
    _kbd :: [b] -> a
    kbd_ :: [Att11] -> [b] -> a
instance C_Kbd Ent3 Ent60 where
    _kbd = Kbd_3 []
    kbd_  = Kbd_3 
instance C_Kbd Ent4 Ent4 where
    _kbd = Kbd_4 []
    kbd_  = Kbd_4 
instance C_Kbd Ent6 Ent4 where
    _kbd = Kbd_6 []
    kbd_  = Kbd_6 
instance C_Kbd Ent10 Ent4 where
    _kbd = Kbd_10 []
    kbd_  = Kbd_10 
instance C_Kbd Ent12 Ent13 where
    _kbd = Kbd_12 []
    kbd_  = Kbd_12 
instance C_Kbd Ent13 Ent13 where
    _kbd = Kbd_13 []
    kbd_  = Kbd_13 
instance C_Kbd Ent16 Ent13 where
    _kbd = Kbd_16 []
    kbd_  = Kbd_16 
instance C_Kbd Ent17 Ent13 where
    _kbd = Kbd_17 []
    kbd_  = Kbd_17 
instance C_Kbd Ent22 Ent4 where
    _kbd = Kbd_22 []
    kbd_  = Kbd_22 
instance C_Kbd Ent27 Ent4 where
    _kbd = Kbd_27 []
    kbd_  = Kbd_27 
instance C_Kbd Ent29 Ent29 where
    _kbd = Kbd_29 []
    kbd_  = Kbd_29 
instance C_Kbd Ent31 Ent29 where
    _kbd = Kbd_31 []
    kbd_  = Kbd_31 
instance C_Kbd Ent35 Ent29 where
    _kbd = Kbd_35 []
    kbd_  = Kbd_35 
instance C_Kbd Ent37 Ent38 where
    _kbd = Kbd_37 []
    kbd_  = Kbd_37 
instance C_Kbd Ent38 Ent38 where
    _kbd = Kbd_38 []
    kbd_  = Kbd_38 
instance C_Kbd Ent41 Ent38 where
    _kbd = Kbd_41 []
    kbd_  = Kbd_41 
instance C_Kbd Ent42 Ent38 where
    _kbd = Kbd_42 []
    kbd_  = Kbd_42 
instance C_Kbd Ent47 Ent29 where
    _kbd = Kbd_47 []
    kbd_  = Kbd_47 
instance C_Kbd Ent52 Ent29 where
    _kbd = Kbd_52 []
    kbd_  = Kbd_52 
instance C_Kbd Ent56 Ent29 where
    _kbd = Kbd_56 []
    kbd_  = Kbd_56 
instance C_Kbd Ent59 Ent4 where
    _kbd = Kbd_59 []
    kbd_  = Kbd_59 
instance C_Kbd Ent60 Ent60 where
    _kbd = Kbd_60 []
    kbd_  = Kbd_60 
instance C_Kbd Ent62 Ent62 where
    _kbd = Kbd_62 []
    kbd_  = Kbd_62 
instance C_Kbd Ent64 Ent62 where
    _kbd = Kbd_64 []
    kbd_  = Kbd_64 
instance C_Kbd Ent68 Ent62 where
    _kbd = Kbd_68 []
    kbd_  = Kbd_68 
instance C_Kbd Ent70 Ent71 where
    _kbd = Kbd_70 []
    kbd_  = Kbd_70 
instance C_Kbd Ent71 Ent71 where
    _kbd = Kbd_71 []
    kbd_  = Kbd_71 
instance C_Kbd Ent74 Ent71 where
    _kbd = Kbd_74 []
    kbd_  = Kbd_74 
instance C_Kbd Ent75 Ent71 where
    _kbd = Kbd_75 []
    kbd_  = Kbd_75 
instance C_Kbd Ent80 Ent62 where
    _kbd = Kbd_80 []
    kbd_  = Kbd_80 
instance C_Kbd Ent85 Ent62 where
    _kbd = Kbd_85 []
    kbd_  = Kbd_85 
instance C_Kbd Ent89 Ent62 where
    _kbd = Kbd_89 []
    kbd_  = Kbd_89 
instance C_Kbd Ent92 Ent60 where
    _kbd = Kbd_92 []
    kbd_  = Kbd_92 
instance C_Kbd Ent94 Ent60 where
    _kbd = Kbd_94 []
    kbd_  = Kbd_94 
instance C_Kbd Ent97 Ent60 where
    _kbd = Kbd_97 []
    kbd_  = Kbd_97 
instance C_Kbd Ent100 Ent113 where
    _kbd = Kbd_100 []
    kbd_  = Kbd_100 
instance C_Kbd Ent102 Ent13 where
    _kbd = Kbd_102 []
    kbd_  = Kbd_102 
instance C_Kbd Ent105 Ent38 where
    _kbd = Kbd_105 []
    kbd_  = Kbd_105 
instance C_Kbd Ent109 Ent38 where
    _kbd = Kbd_109 []
    kbd_  = Kbd_109 
instance C_Kbd Ent112 Ent13 where
    _kbd = Kbd_112 []
    kbd_  = Kbd_112 
instance C_Kbd Ent113 Ent113 where
    _kbd = Kbd_113 []
    kbd_  = Kbd_113 
instance C_Kbd Ent114 Ent113 where
    _kbd = Kbd_114 []
    kbd_  = Kbd_114 
instance C_Kbd Ent117 Ent71 where
    _kbd = Kbd_117 []
    kbd_  = Kbd_117 
instance C_Kbd Ent121 Ent71 where
    _kbd = Kbd_121 []
    kbd_  = Kbd_121 
instance C_Kbd Ent124 Ent113 where
    _kbd = Kbd_124 []
    kbd_  = Kbd_124 
instance C_Kbd Ent127 Ent113 where
    _kbd = Kbd_127 []
    kbd_  = Kbd_127 
instance C_Kbd Ent128 Ent113 where
    _kbd = Kbd_128 []
    kbd_  = Kbd_128 
instance C_Kbd Ent133 Ent60 where
    _kbd = Kbd_133 []
    kbd_  = Kbd_133 

class C_Var a b | a -> b where
    _var :: [b] -> a
    var_ :: [Att11] -> [b] -> a
instance C_Var Ent3 Ent60 where
    _var = Var_3 []
    var_  = Var_3 
instance C_Var Ent4 Ent4 where
    _var = Var_4 []
    var_  = Var_4 
instance C_Var Ent6 Ent4 where
    _var = Var_6 []
    var_  = Var_6 
instance C_Var Ent10 Ent4 where
    _var = Var_10 []
    var_  = Var_10 
instance C_Var Ent12 Ent13 where
    _var = Var_12 []
    var_  = Var_12 
instance C_Var Ent13 Ent13 where
    _var = Var_13 []
    var_  = Var_13 
instance C_Var Ent16 Ent13 where
    _var = Var_16 []
    var_  = Var_16 
instance C_Var Ent17 Ent13 where
    _var = Var_17 []
    var_  = Var_17 
instance C_Var Ent22 Ent4 where
    _var = Var_22 []
    var_  = Var_22 
instance C_Var Ent27 Ent4 where
    _var = Var_27 []
    var_  = Var_27 
instance C_Var Ent29 Ent29 where
    _var = Var_29 []
    var_  = Var_29 
instance C_Var Ent31 Ent29 where
    _var = Var_31 []
    var_  = Var_31 
instance C_Var Ent35 Ent29 where
    _var = Var_35 []
    var_  = Var_35 
instance C_Var Ent37 Ent38 where
    _var = Var_37 []
    var_  = Var_37 
instance C_Var Ent38 Ent38 where
    _var = Var_38 []
    var_  = Var_38 
instance C_Var Ent41 Ent38 where
    _var = Var_41 []
    var_  = Var_41 
instance C_Var Ent42 Ent38 where
    _var = Var_42 []
    var_  = Var_42 
instance C_Var Ent47 Ent29 where
    _var = Var_47 []
    var_  = Var_47 
instance C_Var Ent52 Ent29 where
    _var = Var_52 []
    var_  = Var_52 
instance C_Var Ent56 Ent29 where
    _var = Var_56 []
    var_  = Var_56 
instance C_Var Ent59 Ent4 where
    _var = Var_59 []
    var_  = Var_59 
instance C_Var Ent60 Ent60 where
    _var = Var_60 []
    var_  = Var_60 
instance C_Var Ent62 Ent62 where
    _var = Var_62 []
    var_  = Var_62 
instance C_Var Ent64 Ent62 where
    _var = Var_64 []
    var_  = Var_64 
instance C_Var Ent68 Ent62 where
    _var = Var_68 []
    var_  = Var_68 
instance C_Var Ent70 Ent71 where
    _var = Var_70 []
    var_  = Var_70 
instance C_Var Ent71 Ent71 where
    _var = Var_71 []
    var_  = Var_71 
instance C_Var Ent74 Ent71 where
    _var = Var_74 []
    var_  = Var_74 
instance C_Var Ent75 Ent71 where
    _var = Var_75 []
    var_  = Var_75 
instance C_Var Ent80 Ent62 where
    _var = Var_80 []
    var_  = Var_80 
instance C_Var Ent85 Ent62 where
    _var = Var_85 []
    var_  = Var_85 
instance C_Var Ent89 Ent62 where
    _var = Var_89 []
    var_  = Var_89 
instance C_Var Ent92 Ent60 where
    _var = Var_92 []
    var_  = Var_92 
instance C_Var Ent94 Ent60 where
    _var = Var_94 []
    var_  = Var_94 
instance C_Var Ent97 Ent60 where
    _var = Var_97 []
    var_  = Var_97 
instance C_Var Ent100 Ent113 where
    _var = Var_100 []
    var_  = Var_100 
instance C_Var Ent102 Ent13 where
    _var = Var_102 []
    var_  = Var_102 
instance C_Var Ent105 Ent38 where
    _var = Var_105 []
    var_  = Var_105 
instance C_Var Ent109 Ent38 where
    _var = Var_109 []
    var_  = Var_109 
instance C_Var Ent112 Ent13 where
    _var = Var_112 []
    var_  = Var_112 
instance C_Var Ent113 Ent113 where
    _var = Var_113 []
    var_  = Var_113 
instance C_Var Ent114 Ent113 where
    _var = Var_114 []
    var_  = Var_114 
instance C_Var Ent117 Ent71 where
    _var = Var_117 []
    var_  = Var_117 
instance C_Var Ent121 Ent71 where
    _var = Var_121 []
    var_  = Var_121 
instance C_Var Ent124 Ent113 where
    _var = Var_124 []
    var_  = Var_124 
instance C_Var Ent127 Ent113 where
    _var = Var_127 []
    var_  = Var_127 
instance C_Var Ent128 Ent113 where
    _var = Var_128 []
    var_  = Var_128 
instance C_Var Ent133 Ent60 where
    _var = Var_133 []
    var_  = Var_133 

class C_Cite a b | a -> b where
    _cite :: [b] -> a
    cite_ :: [Att11] -> [b] -> a
instance C_Cite Ent3 Ent60 where
    _cite = Cite_3 []
    cite_  = Cite_3 
instance C_Cite Ent4 Ent4 where
    _cite = Cite_4 []
    cite_  = Cite_4 
instance C_Cite Ent6 Ent4 where
    _cite = Cite_6 []
    cite_  = Cite_6 
instance C_Cite Ent10 Ent4 where
    _cite = Cite_10 []
    cite_  = Cite_10 
instance C_Cite Ent12 Ent13 where
    _cite = Cite_12 []
    cite_  = Cite_12 
instance C_Cite Ent13 Ent13 where
    _cite = Cite_13 []
    cite_  = Cite_13 
instance C_Cite Ent16 Ent13 where
    _cite = Cite_16 []
    cite_  = Cite_16 
instance C_Cite Ent17 Ent13 where
    _cite = Cite_17 []
    cite_  = Cite_17 
instance C_Cite Ent22 Ent4 where
    _cite = Cite_22 []
    cite_  = Cite_22 
instance C_Cite Ent27 Ent4 where
    _cite = Cite_27 []
    cite_  = Cite_27 
instance C_Cite Ent29 Ent29 where
    _cite = Cite_29 []
    cite_  = Cite_29 
instance C_Cite Ent31 Ent29 where
    _cite = Cite_31 []
    cite_  = Cite_31 
instance C_Cite Ent35 Ent29 where
    _cite = Cite_35 []
    cite_  = Cite_35 
instance C_Cite Ent37 Ent38 where
    _cite = Cite_37 []
    cite_  = Cite_37 
instance C_Cite Ent38 Ent38 where
    _cite = Cite_38 []
    cite_  = Cite_38 
instance C_Cite Ent41 Ent38 where
    _cite = Cite_41 []
    cite_  = Cite_41 
instance C_Cite Ent42 Ent38 where
    _cite = Cite_42 []
    cite_  = Cite_42 
instance C_Cite Ent47 Ent29 where
    _cite = Cite_47 []
    cite_  = Cite_47 
instance C_Cite Ent52 Ent29 where
    _cite = Cite_52 []
    cite_  = Cite_52 
instance C_Cite Ent56 Ent29 where
    _cite = Cite_56 []
    cite_  = Cite_56 
instance C_Cite Ent59 Ent4 where
    _cite = Cite_59 []
    cite_  = Cite_59 
instance C_Cite Ent60 Ent60 where
    _cite = Cite_60 []
    cite_  = Cite_60 
instance C_Cite Ent62 Ent62 where
    _cite = Cite_62 []
    cite_  = Cite_62 
instance C_Cite Ent64 Ent62 where
    _cite = Cite_64 []
    cite_  = Cite_64 
instance C_Cite Ent68 Ent62 where
    _cite = Cite_68 []
    cite_  = Cite_68 
instance C_Cite Ent70 Ent71 where
    _cite = Cite_70 []
    cite_  = Cite_70 
instance C_Cite Ent71 Ent71 where
    _cite = Cite_71 []
    cite_  = Cite_71 
instance C_Cite Ent74 Ent71 where
    _cite = Cite_74 []
    cite_  = Cite_74 
instance C_Cite Ent75 Ent71 where
    _cite = Cite_75 []
    cite_  = Cite_75 
instance C_Cite Ent80 Ent62 where
    _cite = Cite_80 []
    cite_  = Cite_80 
instance C_Cite Ent85 Ent62 where
    _cite = Cite_85 []
    cite_  = Cite_85 
instance C_Cite Ent89 Ent62 where
    _cite = Cite_89 []
    cite_  = Cite_89 
instance C_Cite Ent92 Ent60 where
    _cite = Cite_92 []
    cite_  = Cite_92 
instance C_Cite Ent94 Ent60 where
    _cite = Cite_94 []
    cite_  = Cite_94 
instance C_Cite Ent97 Ent60 where
    _cite = Cite_97 []
    cite_  = Cite_97 
instance C_Cite Ent100 Ent113 where
    _cite = Cite_100 []
    cite_  = Cite_100 
instance C_Cite Ent102 Ent13 where
    _cite = Cite_102 []
    cite_  = Cite_102 
instance C_Cite Ent105 Ent38 where
    _cite = Cite_105 []
    cite_  = Cite_105 
instance C_Cite Ent109 Ent38 where
    _cite = Cite_109 []
    cite_  = Cite_109 
instance C_Cite Ent112 Ent13 where
    _cite = Cite_112 []
    cite_  = Cite_112 
instance C_Cite Ent113 Ent113 where
    _cite = Cite_113 []
    cite_  = Cite_113 
instance C_Cite Ent114 Ent113 where
    _cite = Cite_114 []
    cite_  = Cite_114 
instance C_Cite Ent117 Ent71 where
    _cite = Cite_117 []
    cite_  = Cite_117 
instance C_Cite Ent121 Ent71 where
    _cite = Cite_121 []
    cite_  = Cite_121 
instance C_Cite Ent124 Ent113 where
    _cite = Cite_124 []
    cite_  = Cite_124 
instance C_Cite Ent127 Ent113 where
    _cite = Cite_127 []
    cite_  = Cite_127 
instance C_Cite Ent128 Ent113 where
    _cite = Cite_128 []
    cite_  = Cite_128 
instance C_Cite Ent133 Ent60 where
    _cite = Cite_133 []
    cite_  = Cite_133 

class C_Abbr a b | a -> b where
    _abbr :: [b] -> a
    abbr_ :: [Att11] -> [b] -> a
instance C_Abbr Ent3 Ent60 where
    _abbr = Abbr_3 []
    abbr_  = Abbr_3 
instance C_Abbr Ent4 Ent4 where
    _abbr = Abbr_4 []
    abbr_  = Abbr_4 
instance C_Abbr Ent6 Ent4 where
    _abbr = Abbr_6 []
    abbr_  = Abbr_6 
instance C_Abbr Ent10 Ent4 where
    _abbr = Abbr_10 []
    abbr_  = Abbr_10 
instance C_Abbr Ent12 Ent13 where
    _abbr = Abbr_12 []
    abbr_  = Abbr_12 
instance C_Abbr Ent13 Ent13 where
    _abbr = Abbr_13 []
    abbr_  = Abbr_13 
instance C_Abbr Ent16 Ent13 where
    _abbr = Abbr_16 []
    abbr_  = Abbr_16 
instance C_Abbr Ent17 Ent13 where
    _abbr = Abbr_17 []
    abbr_  = Abbr_17 
instance C_Abbr Ent22 Ent4 where
    _abbr = Abbr_22 []
    abbr_  = Abbr_22 
instance C_Abbr Ent27 Ent4 where
    _abbr = Abbr_27 []
    abbr_  = Abbr_27 
instance C_Abbr Ent29 Ent29 where
    _abbr = Abbr_29 []
    abbr_  = Abbr_29 
instance C_Abbr Ent31 Ent29 where
    _abbr = Abbr_31 []
    abbr_  = Abbr_31 
instance C_Abbr Ent35 Ent29 where
    _abbr = Abbr_35 []
    abbr_  = Abbr_35 
instance C_Abbr Ent37 Ent38 where
    _abbr = Abbr_37 []
    abbr_  = Abbr_37 
instance C_Abbr Ent38 Ent38 where
    _abbr = Abbr_38 []
    abbr_  = Abbr_38 
instance C_Abbr Ent41 Ent38 where
    _abbr = Abbr_41 []
    abbr_  = Abbr_41 
instance C_Abbr Ent42 Ent38 where
    _abbr = Abbr_42 []
    abbr_  = Abbr_42 
instance C_Abbr Ent47 Ent29 where
    _abbr = Abbr_47 []
    abbr_  = Abbr_47 
instance C_Abbr Ent52 Ent29 where
    _abbr = Abbr_52 []
    abbr_  = Abbr_52 
instance C_Abbr Ent56 Ent29 where
    _abbr = Abbr_56 []
    abbr_  = Abbr_56 
instance C_Abbr Ent59 Ent4 where
    _abbr = Abbr_59 []
    abbr_  = Abbr_59 
instance C_Abbr Ent60 Ent60 where
    _abbr = Abbr_60 []
    abbr_  = Abbr_60 
instance C_Abbr Ent62 Ent62 where
    _abbr = Abbr_62 []
    abbr_  = Abbr_62 
instance C_Abbr Ent64 Ent62 where
    _abbr = Abbr_64 []
    abbr_  = Abbr_64 
instance C_Abbr Ent68 Ent62 where
    _abbr = Abbr_68 []
    abbr_  = Abbr_68 
instance C_Abbr Ent70 Ent71 where
    _abbr = Abbr_70 []
    abbr_  = Abbr_70 
instance C_Abbr Ent71 Ent71 where
    _abbr = Abbr_71 []
    abbr_  = Abbr_71 
instance C_Abbr Ent74 Ent71 where
    _abbr = Abbr_74 []
    abbr_  = Abbr_74 
instance C_Abbr Ent75 Ent71 where
    _abbr = Abbr_75 []
    abbr_  = Abbr_75 
instance C_Abbr Ent80 Ent62 where
    _abbr = Abbr_80 []
    abbr_  = Abbr_80 
instance C_Abbr Ent85 Ent62 where
    _abbr = Abbr_85 []
    abbr_  = Abbr_85 
instance C_Abbr Ent89 Ent62 where
    _abbr = Abbr_89 []
    abbr_  = Abbr_89 
instance C_Abbr Ent92 Ent60 where
    _abbr = Abbr_92 []
    abbr_  = Abbr_92 
instance C_Abbr Ent94 Ent60 where
    _abbr = Abbr_94 []
    abbr_  = Abbr_94 
instance C_Abbr Ent97 Ent60 where
    _abbr = Abbr_97 []
    abbr_  = Abbr_97 
instance C_Abbr Ent100 Ent113 where
    _abbr = Abbr_100 []
    abbr_  = Abbr_100 
instance C_Abbr Ent102 Ent13 where
    _abbr = Abbr_102 []
    abbr_  = Abbr_102 
instance C_Abbr Ent105 Ent38 where
    _abbr = Abbr_105 []
    abbr_  = Abbr_105 
instance C_Abbr Ent109 Ent38 where
    _abbr = Abbr_109 []
    abbr_  = Abbr_109 
instance C_Abbr Ent112 Ent13 where
    _abbr = Abbr_112 []
    abbr_  = Abbr_112 
instance C_Abbr Ent113 Ent113 where
    _abbr = Abbr_113 []
    abbr_  = Abbr_113 
instance C_Abbr Ent114 Ent113 where
    _abbr = Abbr_114 []
    abbr_  = Abbr_114 
instance C_Abbr Ent117 Ent71 where
    _abbr = Abbr_117 []
    abbr_  = Abbr_117 
instance C_Abbr Ent121 Ent71 where
    _abbr = Abbr_121 []
    abbr_  = Abbr_121 
instance C_Abbr Ent124 Ent113 where
    _abbr = Abbr_124 []
    abbr_  = Abbr_124 
instance C_Abbr Ent127 Ent113 where
    _abbr = Abbr_127 []
    abbr_  = Abbr_127 
instance C_Abbr Ent128 Ent113 where
    _abbr = Abbr_128 []
    abbr_  = Abbr_128 
instance C_Abbr Ent133 Ent60 where
    _abbr = Abbr_133 []
    abbr_  = Abbr_133 

class C_Acronym a b | a -> b where
    _acronym :: [b] -> a
    acronym_ :: [Att11] -> [b] -> a
instance C_Acronym Ent3 Ent60 where
    _acronym = Acronym_3 []
    acronym_  = Acronym_3 
instance C_Acronym Ent4 Ent4 where
    _acronym = Acronym_4 []
    acronym_  = Acronym_4 
instance C_Acronym Ent6 Ent4 where
    _acronym = Acronym_6 []
    acronym_  = Acronym_6 
instance C_Acronym Ent10 Ent4 where
    _acronym = Acronym_10 []
    acronym_  = Acronym_10 
instance C_Acronym Ent12 Ent13 where
    _acronym = Acronym_12 []
    acronym_  = Acronym_12 
instance C_Acronym Ent13 Ent13 where
    _acronym = Acronym_13 []
    acronym_  = Acronym_13 
instance C_Acronym Ent16 Ent13 where
    _acronym = Acronym_16 []
    acronym_  = Acronym_16 
instance C_Acronym Ent17 Ent13 where
    _acronym = Acronym_17 []
    acronym_  = Acronym_17 
instance C_Acronym Ent22 Ent4 where
    _acronym = Acronym_22 []
    acronym_  = Acronym_22 
instance C_Acronym Ent27 Ent4 where
    _acronym = Acronym_27 []
    acronym_  = Acronym_27 
instance C_Acronym Ent29 Ent29 where
    _acronym = Acronym_29 []
    acronym_  = Acronym_29 
instance C_Acronym Ent31 Ent29 where
    _acronym = Acronym_31 []
    acronym_  = Acronym_31 
instance C_Acronym Ent35 Ent29 where
    _acronym = Acronym_35 []
    acronym_  = Acronym_35 
instance C_Acronym Ent37 Ent38 where
    _acronym = Acronym_37 []
    acronym_  = Acronym_37 
instance C_Acronym Ent38 Ent38 where
    _acronym = Acronym_38 []
    acronym_  = Acronym_38 
instance C_Acronym Ent41 Ent38 where
    _acronym = Acronym_41 []
    acronym_  = Acronym_41 
instance C_Acronym Ent42 Ent38 where
    _acronym = Acronym_42 []
    acronym_  = Acronym_42 
instance C_Acronym Ent47 Ent29 where
    _acronym = Acronym_47 []
    acronym_  = Acronym_47 
instance C_Acronym Ent52 Ent29 where
    _acronym = Acronym_52 []
    acronym_  = Acronym_52 
instance C_Acronym Ent56 Ent29 where
    _acronym = Acronym_56 []
    acronym_  = Acronym_56 
instance C_Acronym Ent59 Ent4 where
    _acronym = Acronym_59 []
    acronym_  = Acronym_59 
instance C_Acronym Ent60 Ent60 where
    _acronym = Acronym_60 []
    acronym_  = Acronym_60 
instance C_Acronym Ent62 Ent62 where
    _acronym = Acronym_62 []
    acronym_  = Acronym_62 
instance C_Acronym Ent64 Ent62 where
    _acronym = Acronym_64 []
    acronym_  = Acronym_64 
instance C_Acronym Ent68 Ent62 where
    _acronym = Acronym_68 []
    acronym_  = Acronym_68 
instance C_Acronym Ent70 Ent71 where
    _acronym = Acronym_70 []
    acronym_  = Acronym_70 
instance C_Acronym Ent71 Ent71 where
    _acronym = Acronym_71 []
    acronym_  = Acronym_71 
instance C_Acronym Ent74 Ent71 where
    _acronym = Acronym_74 []
    acronym_  = Acronym_74 
instance C_Acronym Ent75 Ent71 where
    _acronym = Acronym_75 []
    acronym_  = Acronym_75 
instance C_Acronym Ent80 Ent62 where
    _acronym = Acronym_80 []
    acronym_  = Acronym_80 
instance C_Acronym Ent85 Ent62 where
    _acronym = Acronym_85 []
    acronym_  = Acronym_85 
instance C_Acronym Ent89 Ent62 where
    _acronym = Acronym_89 []
    acronym_  = Acronym_89 
instance C_Acronym Ent92 Ent60 where
    _acronym = Acronym_92 []
    acronym_  = Acronym_92 
instance C_Acronym Ent94 Ent60 where
    _acronym = Acronym_94 []
    acronym_  = Acronym_94 
instance C_Acronym Ent97 Ent60 where
    _acronym = Acronym_97 []
    acronym_  = Acronym_97 
instance C_Acronym Ent100 Ent113 where
    _acronym = Acronym_100 []
    acronym_  = Acronym_100 
instance C_Acronym Ent102 Ent13 where
    _acronym = Acronym_102 []
    acronym_  = Acronym_102 
instance C_Acronym Ent105 Ent38 where
    _acronym = Acronym_105 []
    acronym_  = Acronym_105 
instance C_Acronym Ent109 Ent38 where
    _acronym = Acronym_109 []
    acronym_  = Acronym_109 
instance C_Acronym Ent112 Ent13 where
    _acronym = Acronym_112 []
    acronym_  = Acronym_112 
instance C_Acronym Ent113 Ent113 where
    _acronym = Acronym_113 []
    acronym_  = Acronym_113 
instance C_Acronym Ent114 Ent113 where
    _acronym = Acronym_114 []
    acronym_  = Acronym_114 
instance C_Acronym Ent117 Ent71 where
    _acronym = Acronym_117 []
    acronym_  = Acronym_117 
instance C_Acronym Ent121 Ent71 where
    _acronym = Acronym_121 []
    acronym_  = Acronym_121 
instance C_Acronym Ent124 Ent113 where
    _acronym = Acronym_124 []
    acronym_  = Acronym_124 
instance C_Acronym Ent127 Ent113 where
    _acronym = Acronym_127 []
    acronym_  = Acronym_127 
instance C_Acronym Ent128 Ent113 where
    _acronym = Acronym_128 []
    acronym_  = Acronym_128 
instance C_Acronym Ent133 Ent60 where
    _acronym = Acronym_133 []
    acronym_  = Acronym_133 

class C_Q a b | a -> b where
    _q :: [b] -> a
    q_ :: [Att13] -> [b] -> a
instance C_Q Ent3 Ent60 where
    _q = Q_3 []
    q_  = Q_3 
instance C_Q Ent4 Ent4 where
    _q = Q_4 []
    q_  = Q_4 
instance C_Q Ent6 Ent4 where
    _q = Q_6 []
    q_  = Q_6 
instance C_Q Ent10 Ent4 where
    _q = Q_10 []
    q_  = Q_10 
instance C_Q Ent12 Ent13 where
    _q = Q_12 []
    q_  = Q_12 
instance C_Q Ent13 Ent13 where
    _q = Q_13 []
    q_  = Q_13 
instance C_Q Ent16 Ent13 where
    _q = Q_16 []
    q_  = Q_16 
instance C_Q Ent17 Ent13 where
    _q = Q_17 []
    q_  = Q_17 
instance C_Q Ent22 Ent4 where
    _q = Q_22 []
    q_  = Q_22 
instance C_Q Ent27 Ent4 where
    _q = Q_27 []
    q_  = Q_27 
instance C_Q Ent29 Ent29 where
    _q = Q_29 []
    q_  = Q_29 
instance C_Q Ent31 Ent29 where
    _q = Q_31 []
    q_  = Q_31 
instance C_Q Ent35 Ent29 where
    _q = Q_35 []
    q_  = Q_35 
instance C_Q Ent37 Ent38 where
    _q = Q_37 []
    q_  = Q_37 
instance C_Q Ent38 Ent38 where
    _q = Q_38 []
    q_  = Q_38 
instance C_Q Ent41 Ent38 where
    _q = Q_41 []
    q_  = Q_41 
instance C_Q Ent42 Ent38 where
    _q = Q_42 []
    q_  = Q_42 
instance C_Q Ent47 Ent29 where
    _q = Q_47 []
    q_  = Q_47 
instance C_Q Ent52 Ent29 where
    _q = Q_52 []
    q_  = Q_52 
instance C_Q Ent56 Ent29 where
    _q = Q_56 []
    q_  = Q_56 
instance C_Q Ent59 Ent4 where
    _q = Q_59 []
    q_  = Q_59 
instance C_Q Ent60 Ent60 where
    _q = Q_60 []
    q_  = Q_60 
instance C_Q Ent62 Ent62 where
    _q = Q_62 []
    q_  = Q_62 
instance C_Q Ent64 Ent62 where
    _q = Q_64 []
    q_  = Q_64 
instance C_Q Ent68 Ent62 where
    _q = Q_68 []
    q_  = Q_68 
instance C_Q Ent70 Ent71 where
    _q = Q_70 []
    q_  = Q_70 
instance C_Q Ent71 Ent71 where
    _q = Q_71 []
    q_  = Q_71 
instance C_Q Ent74 Ent71 where
    _q = Q_74 []
    q_  = Q_74 
instance C_Q Ent75 Ent71 where
    _q = Q_75 []
    q_  = Q_75 
instance C_Q Ent80 Ent62 where
    _q = Q_80 []
    q_  = Q_80 
instance C_Q Ent85 Ent62 where
    _q = Q_85 []
    q_  = Q_85 
instance C_Q Ent89 Ent62 where
    _q = Q_89 []
    q_  = Q_89 
instance C_Q Ent92 Ent60 where
    _q = Q_92 []
    q_  = Q_92 
instance C_Q Ent94 Ent60 where
    _q = Q_94 []
    q_  = Q_94 
instance C_Q Ent97 Ent60 where
    _q = Q_97 []
    q_  = Q_97 
instance C_Q Ent100 Ent113 where
    _q = Q_100 []
    q_  = Q_100 
instance C_Q Ent102 Ent13 where
    _q = Q_102 []
    q_  = Q_102 
instance C_Q Ent105 Ent38 where
    _q = Q_105 []
    q_  = Q_105 
instance C_Q Ent109 Ent38 where
    _q = Q_109 []
    q_  = Q_109 
instance C_Q Ent112 Ent13 where
    _q = Q_112 []
    q_  = Q_112 
instance C_Q Ent113 Ent113 where
    _q = Q_113 []
    q_  = Q_113 
instance C_Q Ent114 Ent113 where
    _q = Q_114 []
    q_  = Q_114 
instance C_Q Ent117 Ent71 where
    _q = Q_117 []
    q_  = Q_117 
instance C_Q Ent121 Ent71 where
    _q = Q_121 []
    q_  = Q_121 
instance C_Q Ent124 Ent113 where
    _q = Q_124 []
    q_  = Q_124 
instance C_Q Ent127 Ent113 where
    _q = Q_127 []
    q_  = Q_127 
instance C_Q Ent128 Ent113 where
    _q = Q_128 []
    q_  = Q_128 
instance C_Q Ent133 Ent60 where
    _q = Q_133 []
    q_  = Q_133 

class C_Sub a b | a -> b where
    _sub :: [b] -> a
    sub_ :: [Att11] -> [b] -> a
instance C_Sub Ent3 Ent60 where
    _sub = Sub_3 []
    sub_  = Sub_3 
instance C_Sub Ent4 Ent4 where
    _sub = Sub_4 []
    sub_  = Sub_4 
instance C_Sub Ent6 Ent4 where
    _sub = Sub_6 []
    sub_  = Sub_6 
instance C_Sub Ent10 Ent4 where
    _sub = Sub_10 []
    sub_  = Sub_10 
instance C_Sub Ent12 Ent13 where
    _sub = Sub_12 []
    sub_  = Sub_12 
instance C_Sub Ent13 Ent13 where
    _sub = Sub_13 []
    sub_  = Sub_13 
instance C_Sub Ent16 Ent13 where
    _sub = Sub_16 []
    sub_  = Sub_16 
instance C_Sub Ent17 Ent13 where
    _sub = Sub_17 []
    sub_  = Sub_17 
instance C_Sub Ent22 Ent4 where
    _sub = Sub_22 []
    sub_  = Sub_22 
instance C_Sub Ent27 Ent4 where
    _sub = Sub_27 []
    sub_  = Sub_27 
instance C_Sub Ent29 Ent29 where
    _sub = Sub_29 []
    sub_  = Sub_29 
instance C_Sub Ent31 Ent29 where
    _sub = Sub_31 []
    sub_  = Sub_31 
instance C_Sub Ent35 Ent29 where
    _sub = Sub_35 []
    sub_  = Sub_35 
instance C_Sub Ent37 Ent38 where
    _sub = Sub_37 []
    sub_  = Sub_37 
instance C_Sub Ent38 Ent38 where
    _sub = Sub_38 []
    sub_  = Sub_38 
instance C_Sub Ent41 Ent38 where
    _sub = Sub_41 []
    sub_  = Sub_41 
instance C_Sub Ent42 Ent38 where
    _sub = Sub_42 []
    sub_  = Sub_42 
instance C_Sub Ent47 Ent29 where
    _sub = Sub_47 []
    sub_  = Sub_47 
instance C_Sub Ent52 Ent29 where
    _sub = Sub_52 []
    sub_  = Sub_52 
instance C_Sub Ent56 Ent29 where
    _sub = Sub_56 []
    sub_  = Sub_56 
instance C_Sub Ent59 Ent4 where
    _sub = Sub_59 []
    sub_  = Sub_59 
instance C_Sub Ent60 Ent60 where
    _sub = Sub_60 []
    sub_  = Sub_60 
instance C_Sub Ent62 Ent62 where
    _sub = Sub_62 []
    sub_  = Sub_62 
instance C_Sub Ent64 Ent62 where
    _sub = Sub_64 []
    sub_  = Sub_64 
instance C_Sub Ent68 Ent62 where
    _sub = Sub_68 []
    sub_  = Sub_68 
instance C_Sub Ent70 Ent71 where
    _sub = Sub_70 []
    sub_  = Sub_70 
instance C_Sub Ent71 Ent71 where
    _sub = Sub_71 []
    sub_  = Sub_71 
instance C_Sub Ent74 Ent71 where
    _sub = Sub_74 []
    sub_  = Sub_74 
instance C_Sub Ent75 Ent71 where
    _sub = Sub_75 []
    sub_  = Sub_75 
instance C_Sub Ent80 Ent62 where
    _sub = Sub_80 []
    sub_  = Sub_80 
instance C_Sub Ent85 Ent62 where
    _sub = Sub_85 []
    sub_  = Sub_85 
instance C_Sub Ent89 Ent62 where
    _sub = Sub_89 []
    sub_  = Sub_89 
instance C_Sub Ent92 Ent60 where
    _sub = Sub_92 []
    sub_  = Sub_92 
instance C_Sub Ent94 Ent60 where
    _sub = Sub_94 []
    sub_  = Sub_94 
instance C_Sub Ent97 Ent60 where
    _sub = Sub_97 []
    sub_  = Sub_97 
instance C_Sub Ent100 Ent113 where
    _sub = Sub_100 []
    sub_  = Sub_100 
instance C_Sub Ent102 Ent13 where
    _sub = Sub_102 []
    sub_  = Sub_102 
instance C_Sub Ent105 Ent38 where
    _sub = Sub_105 []
    sub_  = Sub_105 
instance C_Sub Ent109 Ent38 where
    _sub = Sub_109 []
    sub_  = Sub_109 
instance C_Sub Ent112 Ent13 where
    _sub = Sub_112 []
    sub_  = Sub_112 
instance C_Sub Ent113 Ent113 where
    _sub = Sub_113 []
    sub_  = Sub_113 
instance C_Sub Ent114 Ent113 where
    _sub = Sub_114 []
    sub_  = Sub_114 
instance C_Sub Ent117 Ent71 where
    _sub = Sub_117 []
    sub_  = Sub_117 
instance C_Sub Ent121 Ent71 where
    _sub = Sub_121 []
    sub_  = Sub_121 
instance C_Sub Ent124 Ent113 where
    _sub = Sub_124 []
    sub_  = Sub_124 
instance C_Sub Ent127 Ent113 where
    _sub = Sub_127 []
    sub_  = Sub_127 
instance C_Sub Ent128 Ent113 where
    _sub = Sub_128 []
    sub_  = Sub_128 
instance C_Sub Ent133 Ent60 where
    _sub = Sub_133 []
    sub_  = Sub_133 

class C_Sup a b | a -> b where
    _sup :: [b] -> a
    sup_ :: [Att11] -> [b] -> a
instance C_Sup Ent3 Ent60 where
    _sup = Sup_3 []
    sup_  = Sup_3 
instance C_Sup Ent4 Ent4 where
    _sup = Sup_4 []
    sup_  = Sup_4 
instance C_Sup Ent6 Ent4 where
    _sup = Sup_6 []
    sup_  = Sup_6 
instance C_Sup Ent10 Ent4 where
    _sup = Sup_10 []
    sup_  = Sup_10 
instance C_Sup Ent12 Ent13 where
    _sup = Sup_12 []
    sup_  = Sup_12 
instance C_Sup Ent13 Ent13 where
    _sup = Sup_13 []
    sup_  = Sup_13 
instance C_Sup Ent16 Ent13 where
    _sup = Sup_16 []
    sup_  = Sup_16 
instance C_Sup Ent17 Ent13 where
    _sup = Sup_17 []
    sup_  = Sup_17 
instance C_Sup Ent22 Ent4 where
    _sup = Sup_22 []
    sup_  = Sup_22 
instance C_Sup Ent27 Ent4 where
    _sup = Sup_27 []
    sup_  = Sup_27 
instance C_Sup Ent29 Ent29 where
    _sup = Sup_29 []
    sup_  = Sup_29 
instance C_Sup Ent31 Ent29 where
    _sup = Sup_31 []
    sup_  = Sup_31 
instance C_Sup Ent35 Ent29 where
    _sup = Sup_35 []
    sup_  = Sup_35 
instance C_Sup Ent37 Ent38 where
    _sup = Sup_37 []
    sup_  = Sup_37 
instance C_Sup Ent38 Ent38 where
    _sup = Sup_38 []
    sup_  = Sup_38 
instance C_Sup Ent41 Ent38 where
    _sup = Sup_41 []
    sup_  = Sup_41 
instance C_Sup Ent42 Ent38 where
    _sup = Sup_42 []
    sup_  = Sup_42 
instance C_Sup Ent47 Ent29 where
    _sup = Sup_47 []
    sup_  = Sup_47 
instance C_Sup Ent52 Ent29 where
    _sup = Sup_52 []
    sup_  = Sup_52 
instance C_Sup Ent56 Ent29 where
    _sup = Sup_56 []
    sup_  = Sup_56 
instance C_Sup Ent59 Ent4 where
    _sup = Sup_59 []
    sup_  = Sup_59 
instance C_Sup Ent60 Ent60 where
    _sup = Sup_60 []
    sup_  = Sup_60 
instance C_Sup Ent62 Ent62 where
    _sup = Sup_62 []
    sup_  = Sup_62 
instance C_Sup Ent64 Ent62 where
    _sup = Sup_64 []
    sup_  = Sup_64 
instance C_Sup Ent68 Ent62 where
    _sup = Sup_68 []
    sup_  = Sup_68 
instance C_Sup Ent70 Ent71 where
    _sup = Sup_70 []
    sup_  = Sup_70 
instance C_Sup Ent71 Ent71 where
    _sup = Sup_71 []
    sup_  = Sup_71 
instance C_Sup Ent74 Ent71 where
    _sup = Sup_74 []
    sup_  = Sup_74 
instance C_Sup Ent75 Ent71 where
    _sup = Sup_75 []
    sup_  = Sup_75 
instance C_Sup Ent80 Ent62 where
    _sup = Sup_80 []
    sup_  = Sup_80 
instance C_Sup Ent85 Ent62 where
    _sup = Sup_85 []
    sup_  = Sup_85 
instance C_Sup Ent89 Ent62 where
    _sup = Sup_89 []
    sup_  = Sup_89 
instance C_Sup Ent92 Ent60 where
    _sup = Sup_92 []
    sup_  = Sup_92 
instance C_Sup Ent94 Ent60 where
    _sup = Sup_94 []
    sup_  = Sup_94 
instance C_Sup Ent97 Ent60 where
    _sup = Sup_97 []
    sup_  = Sup_97 
instance C_Sup Ent100 Ent113 where
    _sup = Sup_100 []
    sup_  = Sup_100 
instance C_Sup Ent102 Ent13 where
    _sup = Sup_102 []
    sup_  = Sup_102 
instance C_Sup Ent105 Ent38 where
    _sup = Sup_105 []
    sup_  = Sup_105 
instance C_Sup Ent109 Ent38 where
    _sup = Sup_109 []
    sup_  = Sup_109 
instance C_Sup Ent112 Ent13 where
    _sup = Sup_112 []
    sup_  = Sup_112 
instance C_Sup Ent113 Ent113 where
    _sup = Sup_113 []
    sup_  = Sup_113 
instance C_Sup Ent114 Ent113 where
    _sup = Sup_114 []
    sup_  = Sup_114 
instance C_Sup Ent117 Ent71 where
    _sup = Sup_117 []
    sup_  = Sup_117 
instance C_Sup Ent121 Ent71 where
    _sup = Sup_121 []
    sup_  = Sup_121 
instance C_Sup Ent124 Ent113 where
    _sup = Sup_124 []
    sup_  = Sup_124 
instance C_Sup Ent127 Ent113 where
    _sup = Sup_127 []
    sup_  = Sup_127 
instance C_Sup Ent128 Ent113 where
    _sup = Sup_128 []
    sup_  = Sup_128 
instance C_Sup Ent133 Ent60 where
    _sup = Sup_133 []
    sup_  = Sup_133 

class C_Tt a b | a -> b where
    _tt :: [b] -> a
    tt_ :: [Att11] -> [b] -> a
instance C_Tt Ent3 Ent60 where
    _tt = Tt_3 []
    tt_  = Tt_3 
instance C_Tt Ent4 Ent4 where
    _tt = Tt_4 []
    tt_  = Tt_4 
instance C_Tt Ent6 Ent4 where
    _tt = Tt_6 []
    tt_  = Tt_6 
instance C_Tt Ent10 Ent4 where
    _tt = Tt_10 []
    tt_  = Tt_10 
instance C_Tt Ent12 Ent13 where
    _tt = Tt_12 []
    tt_  = Tt_12 
instance C_Tt Ent13 Ent13 where
    _tt = Tt_13 []
    tt_  = Tt_13 
instance C_Tt Ent16 Ent13 where
    _tt = Tt_16 []
    tt_  = Tt_16 
instance C_Tt Ent17 Ent13 where
    _tt = Tt_17 []
    tt_  = Tt_17 
instance C_Tt Ent22 Ent4 where
    _tt = Tt_22 []
    tt_  = Tt_22 
instance C_Tt Ent27 Ent4 where
    _tt = Tt_27 []
    tt_  = Tt_27 
instance C_Tt Ent29 Ent29 where
    _tt = Tt_29 []
    tt_  = Tt_29 
instance C_Tt Ent31 Ent29 where
    _tt = Tt_31 []
    tt_  = Tt_31 
instance C_Tt Ent35 Ent29 where
    _tt = Tt_35 []
    tt_  = Tt_35 
instance C_Tt Ent37 Ent38 where
    _tt = Tt_37 []
    tt_  = Tt_37 
instance C_Tt Ent38 Ent38 where
    _tt = Tt_38 []
    tt_  = Tt_38 
instance C_Tt Ent41 Ent38 where
    _tt = Tt_41 []
    tt_  = Tt_41 
instance C_Tt Ent42 Ent38 where
    _tt = Tt_42 []
    tt_  = Tt_42 
instance C_Tt Ent47 Ent29 where
    _tt = Tt_47 []
    tt_  = Tt_47 
instance C_Tt Ent52 Ent29 where
    _tt = Tt_52 []
    tt_  = Tt_52 
instance C_Tt Ent56 Ent29 where
    _tt = Tt_56 []
    tt_  = Tt_56 
instance C_Tt Ent59 Ent4 where
    _tt = Tt_59 []
    tt_  = Tt_59 
instance C_Tt Ent60 Ent60 where
    _tt = Tt_60 []
    tt_  = Tt_60 
instance C_Tt Ent62 Ent62 where
    _tt = Tt_62 []
    tt_  = Tt_62 
instance C_Tt Ent64 Ent62 where
    _tt = Tt_64 []
    tt_  = Tt_64 
instance C_Tt Ent68 Ent62 where
    _tt = Tt_68 []
    tt_  = Tt_68 
instance C_Tt Ent70 Ent71 where
    _tt = Tt_70 []
    tt_  = Tt_70 
instance C_Tt Ent71 Ent71 where
    _tt = Tt_71 []
    tt_  = Tt_71 
instance C_Tt Ent74 Ent71 where
    _tt = Tt_74 []
    tt_  = Tt_74 
instance C_Tt Ent75 Ent71 where
    _tt = Tt_75 []
    tt_  = Tt_75 
instance C_Tt Ent80 Ent62 where
    _tt = Tt_80 []
    tt_  = Tt_80 
instance C_Tt Ent85 Ent62 where
    _tt = Tt_85 []
    tt_  = Tt_85 
instance C_Tt Ent89 Ent62 where
    _tt = Tt_89 []
    tt_  = Tt_89 
instance C_Tt Ent92 Ent60 where
    _tt = Tt_92 []
    tt_  = Tt_92 
instance C_Tt Ent94 Ent60 where
    _tt = Tt_94 []
    tt_  = Tt_94 
instance C_Tt Ent97 Ent60 where
    _tt = Tt_97 []
    tt_  = Tt_97 
instance C_Tt Ent100 Ent113 where
    _tt = Tt_100 []
    tt_  = Tt_100 
instance C_Tt Ent102 Ent13 where
    _tt = Tt_102 []
    tt_  = Tt_102 
instance C_Tt Ent105 Ent38 where
    _tt = Tt_105 []
    tt_  = Tt_105 
instance C_Tt Ent109 Ent38 where
    _tt = Tt_109 []
    tt_  = Tt_109 
instance C_Tt Ent112 Ent13 where
    _tt = Tt_112 []
    tt_  = Tt_112 
instance C_Tt Ent113 Ent113 where
    _tt = Tt_113 []
    tt_  = Tt_113 
instance C_Tt Ent114 Ent113 where
    _tt = Tt_114 []
    tt_  = Tt_114 
instance C_Tt Ent117 Ent71 where
    _tt = Tt_117 []
    tt_  = Tt_117 
instance C_Tt Ent121 Ent71 where
    _tt = Tt_121 []
    tt_  = Tt_121 
instance C_Tt Ent124 Ent113 where
    _tt = Tt_124 []
    tt_  = Tt_124 
instance C_Tt Ent127 Ent113 where
    _tt = Tt_127 []
    tt_  = Tt_127 
instance C_Tt Ent128 Ent113 where
    _tt = Tt_128 []
    tt_  = Tt_128 
instance C_Tt Ent133 Ent60 where
    _tt = Tt_133 []
    tt_  = Tt_133 

class C_I a b | a -> b where
    _i :: [b] -> a
    i_ :: [Att11] -> [b] -> a
instance C_I Ent3 Ent60 where
    _i = I_3 []
    i_  = I_3 
instance C_I Ent4 Ent4 where
    _i = I_4 []
    i_  = I_4 
instance C_I Ent6 Ent4 where
    _i = I_6 []
    i_  = I_6 
instance C_I Ent10 Ent4 where
    _i = I_10 []
    i_  = I_10 
instance C_I Ent12 Ent13 where
    _i = I_12 []
    i_  = I_12 
instance C_I Ent13 Ent13 where
    _i = I_13 []
    i_  = I_13 
instance C_I Ent16 Ent13 where
    _i = I_16 []
    i_  = I_16 
instance C_I Ent17 Ent13 where
    _i = I_17 []
    i_  = I_17 
instance C_I Ent22 Ent4 where
    _i = I_22 []
    i_  = I_22 
instance C_I Ent27 Ent4 where
    _i = I_27 []
    i_  = I_27 
instance C_I Ent29 Ent29 where
    _i = I_29 []
    i_  = I_29 
instance C_I Ent31 Ent29 where
    _i = I_31 []
    i_  = I_31 
instance C_I Ent35 Ent29 where
    _i = I_35 []
    i_  = I_35 
instance C_I Ent37 Ent38 where
    _i = I_37 []
    i_  = I_37 
instance C_I Ent38 Ent38 where
    _i = I_38 []
    i_  = I_38 
instance C_I Ent41 Ent38 where
    _i = I_41 []
    i_  = I_41 
instance C_I Ent42 Ent38 where
    _i = I_42 []
    i_  = I_42 
instance C_I Ent47 Ent29 where
    _i = I_47 []
    i_  = I_47 
instance C_I Ent52 Ent29 where
    _i = I_52 []
    i_  = I_52 
instance C_I Ent56 Ent29 where
    _i = I_56 []
    i_  = I_56 
instance C_I Ent59 Ent4 where
    _i = I_59 []
    i_  = I_59 
instance C_I Ent60 Ent60 where
    _i = I_60 []
    i_  = I_60 
instance C_I Ent62 Ent62 where
    _i = I_62 []
    i_  = I_62 
instance C_I Ent64 Ent62 where
    _i = I_64 []
    i_  = I_64 
instance C_I Ent68 Ent62 where
    _i = I_68 []
    i_  = I_68 
instance C_I Ent70 Ent71 where
    _i = I_70 []
    i_  = I_70 
instance C_I Ent71 Ent71 where
    _i = I_71 []
    i_  = I_71 
instance C_I Ent74 Ent71 where
    _i = I_74 []
    i_  = I_74 
instance C_I Ent75 Ent71 where
    _i = I_75 []
    i_  = I_75 
instance C_I Ent80 Ent62 where
    _i = I_80 []
    i_  = I_80 
instance C_I Ent85 Ent62 where
    _i = I_85 []
    i_  = I_85 
instance C_I Ent89 Ent62 where
    _i = I_89 []
    i_  = I_89 
instance C_I Ent92 Ent60 where
    _i = I_92 []
    i_  = I_92 
instance C_I Ent94 Ent60 where
    _i = I_94 []
    i_  = I_94 
instance C_I Ent97 Ent60 where
    _i = I_97 []
    i_  = I_97 
instance C_I Ent100 Ent113 where
    _i = I_100 []
    i_  = I_100 
instance C_I Ent102 Ent13 where
    _i = I_102 []
    i_  = I_102 
instance C_I Ent105 Ent38 where
    _i = I_105 []
    i_  = I_105 
instance C_I Ent109 Ent38 where
    _i = I_109 []
    i_  = I_109 
instance C_I Ent112 Ent13 where
    _i = I_112 []
    i_  = I_112 
instance C_I Ent113 Ent113 where
    _i = I_113 []
    i_  = I_113 
instance C_I Ent114 Ent113 where
    _i = I_114 []
    i_  = I_114 
instance C_I Ent117 Ent71 where
    _i = I_117 []
    i_  = I_117 
instance C_I Ent121 Ent71 where
    _i = I_121 []
    i_  = I_121 
instance C_I Ent124 Ent113 where
    _i = I_124 []
    i_  = I_124 
instance C_I Ent127 Ent113 where
    _i = I_127 []
    i_  = I_127 
instance C_I Ent128 Ent113 where
    _i = I_128 []
    i_  = I_128 
instance C_I Ent133 Ent60 where
    _i = I_133 []
    i_  = I_133 

class C_B a b | a -> b where
    _b :: [b] -> a
    b_ :: [Att11] -> [b] -> a
instance C_B Ent3 Ent60 where
    _b = B_3 []
    b_  = B_3 
instance C_B Ent4 Ent4 where
    _b = B_4 []
    b_  = B_4 
instance C_B Ent6 Ent4 where
    _b = B_6 []
    b_  = B_6 
instance C_B Ent10 Ent4 where
    _b = B_10 []
    b_  = B_10 
instance C_B Ent12 Ent13 where
    _b = B_12 []
    b_  = B_12 
instance C_B Ent13 Ent13 where
    _b = B_13 []
    b_  = B_13 
instance C_B Ent16 Ent13 where
    _b = B_16 []
    b_  = B_16 
instance C_B Ent17 Ent13 where
    _b = B_17 []
    b_  = B_17 
instance C_B Ent22 Ent4 where
    _b = B_22 []
    b_  = B_22 
instance C_B Ent27 Ent4 where
    _b = B_27 []
    b_  = B_27 
instance C_B Ent29 Ent29 where
    _b = B_29 []
    b_  = B_29 
instance C_B Ent31 Ent29 where
    _b = B_31 []
    b_  = B_31 
instance C_B Ent35 Ent29 where
    _b = B_35 []
    b_  = B_35 
instance C_B Ent37 Ent38 where
    _b = B_37 []
    b_  = B_37 
instance C_B Ent38 Ent38 where
    _b = B_38 []
    b_  = B_38 
instance C_B Ent41 Ent38 where
    _b = B_41 []
    b_  = B_41 
instance C_B Ent42 Ent38 where
    _b = B_42 []
    b_  = B_42 
instance C_B Ent47 Ent29 where
    _b = B_47 []
    b_  = B_47 
instance C_B Ent52 Ent29 where
    _b = B_52 []
    b_  = B_52 
instance C_B Ent56 Ent29 where
    _b = B_56 []
    b_  = B_56 
instance C_B Ent59 Ent4 where
    _b = B_59 []
    b_  = B_59 
instance C_B Ent60 Ent60 where
    _b = B_60 []
    b_  = B_60 
instance C_B Ent62 Ent62 where
    _b = B_62 []
    b_  = B_62 
instance C_B Ent64 Ent62 where
    _b = B_64 []
    b_  = B_64 
instance C_B Ent68 Ent62 where
    _b = B_68 []
    b_  = B_68 
instance C_B Ent70 Ent71 where
    _b = B_70 []
    b_  = B_70 
instance C_B Ent71 Ent71 where
    _b = B_71 []
    b_  = B_71 
instance C_B Ent74 Ent71 where
    _b = B_74 []
    b_  = B_74 
instance C_B Ent75 Ent71 where
    _b = B_75 []
    b_  = B_75 
instance C_B Ent80 Ent62 where
    _b = B_80 []
    b_  = B_80 
instance C_B Ent85 Ent62 where
    _b = B_85 []
    b_  = B_85 
instance C_B Ent89 Ent62 where
    _b = B_89 []
    b_  = B_89 
instance C_B Ent92 Ent60 where
    _b = B_92 []
    b_  = B_92 
instance C_B Ent94 Ent60 where
    _b = B_94 []
    b_  = B_94 
instance C_B Ent97 Ent60 where
    _b = B_97 []
    b_  = B_97 
instance C_B Ent100 Ent113 where
    _b = B_100 []
    b_  = B_100 
instance C_B Ent102 Ent13 where
    _b = B_102 []
    b_  = B_102 
instance C_B Ent105 Ent38 where
    _b = B_105 []
    b_  = B_105 
instance C_B Ent109 Ent38 where
    _b = B_109 []
    b_  = B_109 
instance C_B Ent112 Ent13 where
    _b = B_112 []
    b_  = B_112 
instance C_B Ent113 Ent113 where
    _b = B_113 []
    b_  = B_113 
instance C_B Ent114 Ent113 where
    _b = B_114 []
    b_  = B_114 
instance C_B Ent117 Ent71 where
    _b = B_117 []
    b_  = B_117 
instance C_B Ent121 Ent71 where
    _b = B_121 []
    b_  = B_121 
instance C_B Ent124 Ent113 where
    _b = B_124 []
    b_  = B_124 
instance C_B Ent127 Ent113 where
    _b = B_127 []
    b_  = B_127 
instance C_B Ent128 Ent113 where
    _b = B_128 []
    b_  = B_128 
instance C_B Ent133 Ent60 where
    _b = B_133 []
    b_  = B_133 

class C_Big a b | a -> b where
    _big :: [b] -> a
    big_ :: [Att11] -> [b] -> a
instance C_Big Ent3 Ent60 where
    _big = Big_3 []
    big_  = Big_3 
instance C_Big Ent4 Ent4 where
    _big = Big_4 []
    big_  = Big_4 
instance C_Big Ent6 Ent4 where
    _big = Big_6 []
    big_  = Big_6 
instance C_Big Ent10 Ent4 where
    _big = Big_10 []
    big_  = Big_10 
instance C_Big Ent12 Ent13 where
    _big = Big_12 []
    big_  = Big_12 
instance C_Big Ent13 Ent13 where
    _big = Big_13 []
    big_  = Big_13 
instance C_Big Ent16 Ent13 where
    _big = Big_16 []
    big_  = Big_16 
instance C_Big Ent17 Ent13 where
    _big = Big_17 []
    big_  = Big_17 
instance C_Big Ent22 Ent4 where
    _big = Big_22 []
    big_  = Big_22 
instance C_Big Ent27 Ent4 where
    _big = Big_27 []
    big_  = Big_27 
instance C_Big Ent29 Ent29 where
    _big = Big_29 []
    big_  = Big_29 
instance C_Big Ent31 Ent29 where
    _big = Big_31 []
    big_  = Big_31 
instance C_Big Ent35 Ent29 where
    _big = Big_35 []
    big_  = Big_35 
instance C_Big Ent37 Ent38 where
    _big = Big_37 []
    big_  = Big_37 
instance C_Big Ent38 Ent38 where
    _big = Big_38 []
    big_  = Big_38 
instance C_Big Ent41 Ent38 where
    _big = Big_41 []
    big_  = Big_41 
instance C_Big Ent42 Ent38 where
    _big = Big_42 []
    big_  = Big_42 
instance C_Big Ent47 Ent29 where
    _big = Big_47 []
    big_  = Big_47 
instance C_Big Ent52 Ent29 where
    _big = Big_52 []
    big_  = Big_52 
instance C_Big Ent56 Ent29 where
    _big = Big_56 []
    big_  = Big_56 
instance C_Big Ent59 Ent4 where
    _big = Big_59 []
    big_  = Big_59 
instance C_Big Ent60 Ent60 where
    _big = Big_60 []
    big_  = Big_60 
instance C_Big Ent62 Ent62 where
    _big = Big_62 []
    big_  = Big_62 
instance C_Big Ent64 Ent62 where
    _big = Big_64 []
    big_  = Big_64 
instance C_Big Ent68 Ent62 where
    _big = Big_68 []
    big_  = Big_68 
instance C_Big Ent70 Ent71 where
    _big = Big_70 []
    big_  = Big_70 
instance C_Big Ent71 Ent71 where
    _big = Big_71 []
    big_  = Big_71 
instance C_Big Ent74 Ent71 where
    _big = Big_74 []
    big_  = Big_74 
instance C_Big Ent75 Ent71 where
    _big = Big_75 []
    big_  = Big_75 
instance C_Big Ent80 Ent62 where
    _big = Big_80 []
    big_  = Big_80 
instance C_Big Ent85 Ent62 where
    _big = Big_85 []
    big_  = Big_85 
instance C_Big Ent89 Ent62 where
    _big = Big_89 []
    big_  = Big_89 
instance C_Big Ent92 Ent60 where
    _big = Big_92 []
    big_  = Big_92 
instance C_Big Ent94 Ent60 where
    _big = Big_94 []
    big_  = Big_94 
instance C_Big Ent97 Ent60 where
    _big = Big_97 []
    big_  = Big_97 
instance C_Big Ent100 Ent113 where
    _big = Big_100 []
    big_  = Big_100 
instance C_Big Ent102 Ent13 where
    _big = Big_102 []
    big_  = Big_102 
instance C_Big Ent105 Ent38 where
    _big = Big_105 []
    big_  = Big_105 
instance C_Big Ent109 Ent38 where
    _big = Big_109 []
    big_  = Big_109 
instance C_Big Ent112 Ent13 where
    _big = Big_112 []
    big_  = Big_112 
instance C_Big Ent113 Ent113 where
    _big = Big_113 []
    big_  = Big_113 
instance C_Big Ent114 Ent113 where
    _big = Big_114 []
    big_  = Big_114 
instance C_Big Ent117 Ent71 where
    _big = Big_117 []
    big_  = Big_117 
instance C_Big Ent121 Ent71 where
    _big = Big_121 []
    big_  = Big_121 
instance C_Big Ent124 Ent113 where
    _big = Big_124 []
    big_  = Big_124 
instance C_Big Ent127 Ent113 where
    _big = Big_127 []
    big_  = Big_127 
instance C_Big Ent128 Ent113 where
    _big = Big_128 []
    big_  = Big_128 
instance C_Big Ent133 Ent60 where
    _big = Big_133 []
    big_  = Big_133 

class C_Small a b | a -> b where
    _small :: [b] -> a
    small_ :: [Att11] -> [b] -> a
instance C_Small Ent3 Ent60 where
    _small = Small_3 []
    small_  = Small_3 
instance C_Small Ent4 Ent4 where
    _small = Small_4 []
    small_  = Small_4 
instance C_Small Ent6 Ent4 where
    _small = Small_6 []
    small_  = Small_6 
instance C_Small Ent10 Ent4 where
    _small = Small_10 []
    small_  = Small_10 
instance C_Small Ent12 Ent13 where
    _small = Small_12 []
    small_  = Small_12 
instance C_Small Ent13 Ent13 where
    _small = Small_13 []
    small_  = Small_13 
instance C_Small Ent16 Ent13 where
    _small = Small_16 []
    small_  = Small_16 
instance C_Small Ent17 Ent13 where
    _small = Small_17 []
    small_  = Small_17 
instance C_Small Ent22 Ent4 where
    _small = Small_22 []
    small_  = Small_22 
instance C_Small Ent27 Ent4 where
    _small = Small_27 []
    small_  = Small_27 
instance C_Small Ent29 Ent29 where
    _small = Small_29 []
    small_  = Small_29 
instance C_Small Ent31 Ent29 where
    _small = Small_31 []
    small_  = Small_31 
instance C_Small Ent35 Ent29 where
    _small = Small_35 []
    small_  = Small_35 
instance C_Small Ent37 Ent38 where
    _small = Small_37 []
    small_  = Small_37 
instance C_Small Ent38 Ent38 where
    _small = Small_38 []
    small_  = Small_38 
instance C_Small Ent41 Ent38 where
    _small = Small_41 []
    small_  = Small_41 
instance C_Small Ent42 Ent38 where
    _small = Small_42 []
    small_  = Small_42 
instance C_Small Ent47 Ent29 where
    _small = Small_47 []
    small_  = Small_47 
instance C_Small Ent52 Ent29 where
    _small = Small_52 []
    small_  = Small_52 
instance C_Small Ent56 Ent29 where
    _small = Small_56 []
    small_  = Small_56 
instance C_Small Ent59 Ent4 where
    _small = Small_59 []
    small_  = Small_59 
instance C_Small Ent60 Ent60 where
    _small = Small_60 []
    small_  = Small_60 
instance C_Small Ent62 Ent62 where
    _small = Small_62 []
    small_  = Small_62 
instance C_Small Ent64 Ent62 where
    _small = Small_64 []
    small_  = Small_64 
instance C_Small Ent68 Ent62 where
    _small = Small_68 []
    small_  = Small_68 
instance C_Small Ent70 Ent71 where
    _small = Small_70 []
    small_  = Small_70 
instance C_Small Ent71 Ent71 where
    _small = Small_71 []
    small_  = Small_71 
instance C_Small Ent74 Ent71 where
    _small = Small_74 []
    small_  = Small_74 
instance C_Small Ent75 Ent71 where
    _small = Small_75 []
    small_  = Small_75 
instance C_Small Ent80 Ent62 where
    _small = Small_80 []
    small_  = Small_80 
instance C_Small Ent85 Ent62 where
    _small = Small_85 []
    small_  = Small_85 
instance C_Small Ent89 Ent62 where
    _small = Small_89 []
    small_  = Small_89 
instance C_Small Ent92 Ent60 where
    _small = Small_92 []
    small_  = Small_92 
instance C_Small Ent94 Ent60 where
    _small = Small_94 []
    small_  = Small_94 
instance C_Small Ent97 Ent60 where
    _small = Small_97 []
    small_  = Small_97 
instance C_Small Ent100 Ent113 where
    _small = Small_100 []
    small_  = Small_100 
instance C_Small Ent102 Ent13 where
    _small = Small_102 []
    small_  = Small_102 
instance C_Small Ent105 Ent38 where
    _small = Small_105 []
    small_  = Small_105 
instance C_Small Ent109 Ent38 where
    _small = Small_109 []
    small_  = Small_109 
instance C_Small Ent112 Ent13 where
    _small = Small_112 []
    small_  = Small_112 
instance C_Small Ent113 Ent113 where
    _small = Small_113 []
    small_  = Small_113 
instance C_Small Ent114 Ent113 where
    _small = Small_114 []
    small_  = Small_114 
instance C_Small Ent117 Ent71 where
    _small = Small_117 []
    small_  = Small_117 
instance C_Small Ent121 Ent71 where
    _small = Small_121 []
    small_  = Small_121 
instance C_Small Ent124 Ent113 where
    _small = Small_124 []
    small_  = Small_124 
instance C_Small Ent127 Ent113 where
    _small = Small_127 []
    small_  = Small_127 
instance C_Small Ent128 Ent113 where
    _small = Small_128 []
    small_  = Small_128 
instance C_Small Ent133 Ent60 where
    _small = Small_133 []
    small_  = Small_133 

class C_Object a b | a -> b where
    _object :: [b] -> a
    object_ :: [Att19] -> [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 Ent27 where
    _object = Object_4 []
    object_  = Object_4 
instance C_Object Ent6 Ent27 where
    _object = Object_6 []
    object_  = Object_6 
instance C_Object Ent12 Ent102 where
    _object = Object_12 []
    object_  = Object_12 
instance C_Object Ent13 Ent102 where
    _object = Object_13 []
    object_  = Object_13 
instance C_Object Ent17 Ent102 where
    _object = Object_17 []
    object_  = Object_17 
instance C_Object Ent22 Ent27 where
    _object = Object_22 []
    object_  = Object_22 
instance C_Object Ent27 Ent27 where
    _object = Object_27 []
    object_  = Object_27 
instance C_Object Ent29 Ent52 where
    _object = Object_29 []
    object_  = Object_29 
instance C_Object Ent31 Ent52 where
    _object = Object_31 []
    object_  = Object_31 
instance C_Object Ent37 Ent105 where
    _object = Object_37 []
    object_  = Object_37 
instance C_Object Ent38 Ent105 where
    _object = Object_38 []
    object_  = Object_38 
instance C_Object Ent42 Ent105 where
    _object = Object_42 []
    object_  = Object_42 
instance C_Object Ent47 Ent52 where
    _object = Object_47 []
    object_  = Object_47 
instance C_Object Ent52 Ent52 where
    _object = Object_52 []
    object_  = Object_52 
instance C_Object Ent56 Ent52 where
    _object = Object_56 []
    object_  = Object_56 
instance C_Object Ent59 Ent27 where
    _object = Object_59 []
    object_  = Object_59 
instance C_Object Ent60 Ent3 where
    _object = Object_60 []
    object_  = Object_60 
instance C_Object Ent62 Ent85 where
    _object = Object_62 []
    object_  = Object_62 
instance C_Object Ent64 Ent85 where
    _object = Object_64 []
    object_  = Object_64 
instance C_Object Ent70 Ent117 where
    _object = Object_70 []
    object_  = Object_70 
instance C_Object Ent71 Ent117 where
    _object = Object_71 []
    object_  = Object_71 
instance C_Object Ent75 Ent117 where
    _object = Object_75 []
    object_  = Object_75 
instance C_Object Ent80 Ent85 where
    _object = Object_80 []
    object_  = Object_80 
instance C_Object Ent85 Ent85 where
    _object = Object_85 []
    object_  = Object_85 
instance C_Object Ent89 Ent85 where
    _object = Object_89 []
    object_  = Object_89 
instance C_Object Ent92 Ent3 where
    _object = Object_92 []
    object_  = Object_92 
instance C_Object Ent94 Ent3 where
    _object = Object_94 []
    object_  = Object_94 
instance C_Object Ent100 Ent114 where
    _object = Object_100 []
    object_  = Object_100 
instance C_Object Ent102 Ent102 where
    _object = Object_102 []
    object_  = Object_102 
instance C_Object Ent105 Ent105 where
    _object = Object_105 []
    object_  = Object_105 
instance C_Object Ent109 Ent105 where
    _object = Object_109 []
    object_  = Object_109 
instance C_Object Ent112 Ent102 where
    _object = Object_112 []
    object_  = Object_112 
instance C_Object Ent113 Ent114 where
    _object = Object_113 []
    object_  = Object_113 
instance C_Object Ent114 Ent114 where
    _object = Object_114 []
    object_  = Object_114 
instance C_Object Ent117 Ent117 where
    _object = Object_117 []
    object_  = Object_117 
instance C_Object Ent121 Ent117 where
    _object = Object_121 []
    object_  = Object_121 
instance C_Object Ent124 Ent114 where
    _object = Object_124 []
    object_  = Object_124 
instance C_Object Ent128 Ent114 where
    _object = Object_128 []
    object_  = Object_128 
instance C_Object Ent133 Ent3 where
    _object = Object_133 []
    object_  = Object_133 

class C_Param a where
    _param :: a
    param_ :: [Att20] -> a
instance C_Param Ent3 where
    _param = Param_3 []
    param_ = Param_3 
instance C_Param Ent27 where
    _param = Param_27 []
    param_ = Param_27 
instance C_Param Ent52 where
    _param = Param_52 []
    param_ = Param_52 
instance C_Param Ent85 where
    _param = Param_85 []
    param_ = Param_85 
instance C_Param Ent102 where
    _param = Param_102 []
    param_ = Param_102 
instance C_Param Ent105 where
    _param = Param_105 []
    param_ = Param_105 
instance C_Param Ent114 where
    _param = Param_114 []
    param_ = Param_114 
instance C_Param Ent117 where
    _param = Param_117 []
    param_ = Param_117 

class C_Img a where
    _img :: a
    img_ :: [Att21] -> a
instance C_Img Ent3 where
    _img = Img_3 []
    img_ = Img_3 
instance C_Img Ent4 where
    _img = Img_4 []
    img_ = Img_4 
instance C_Img Ent6 where
    _img = Img_6 []
    img_ = Img_6 
instance C_Img Ent12 where
    _img = Img_12 []
    img_ = Img_12 
instance C_Img Ent13 where
    _img = Img_13 []
    img_ = Img_13 
instance C_Img Ent17 where
    _img = Img_17 []
    img_ = Img_17 
instance C_Img Ent22 where
    _img = Img_22 []
    img_ = Img_22 
instance C_Img Ent27 where
    _img = Img_27 []
    img_ = Img_27 
instance C_Img Ent29 where
    _img = Img_29 []
    img_ = Img_29 
instance C_Img Ent31 where
    _img = Img_31 []
    img_ = Img_31 
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 Ent42 where
    _img = Img_42 []
    img_ = Img_42 
instance C_Img Ent47 where
    _img = Img_47 []
    img_ = Img_47 
instance C_Img Ent52 where
    _img = Img_52 []
    img_ = Img_52 
instance C_Img Ent56 where
    _img = Img_56 []
    img_ = Img_56 
instance C_Img Ent59 where
    _img = Img_59 []
    img_ = Img_59 
instance C_Img Ent60 where
    _img = Img_60 []
    img_ = Img_60 
instance C_Img Ent62 where
    _img = Img_62 []
    img_ = Img_62 
instance C_Img Ent64 where
    _img = Img_64 []
    img_ = Img_64 
instance C_Img Ent70 where
    _img = Img_70 []
    img_ = Img_70 
instance C_Img Ent71 where
    _img = Img_71 []
    img_ = Img_71 
instance C_Img Ent75 where
    _img = Img_75 []
    img_ = Img_75 
instance C_Img Ent80 where
    _img = Img_80 []
    img_ = Img_80 
instance C_Img Ent85 where
    _img = Img_85 []
    img_ = Img_85 
instance C_Img Ent89 where
    _img = Img_89 []
    img_ = Img_89 
instance C_Img Ent92 where
    _img = Img_92 []
    img_ = Img_92 
instance C_Img Ent94 where
    _img = Img_94 []
    img_ = Img_94 
instance C_Img Ent100 where
    _img = Img_100 []
    img_ = Img_100 
instance C_Img Ent102 where
    _img = Img_102 []
    img_ = Img_102 
instance C_Img Ent105 where
    _img = Img_105 []
    img_ = Img_105 
instance C_Img Ent109 where
    _img = Img_109 []
    img_ = Img_109 
instance C_Img Ent112 where
    _img = Img_112 []
    img_ = Img_112 
instance C_Img Ent113 where
    _img = Img_113 []
    img_ = Img_113 
instance C_Img Ent114 where
    _img = Img_114 []
    img_ = Img_114 
instance C_Img Ent117 where
    _img = Img_117 []
    img_ = Img_117 
instance C_Img Ent121 where
    _img = Img_121 []
    img_ = Img_121 
instance C_Img Ent124 where
    _img = Img_124 []
    img_ = Img_124 
instance C_Img Ent128 where
    _img = Img_128 []
    img_ = Img_128 
instance C_Img Ent133 where
    _img = Img_133 []
    img_ = Img_133 

class C_Map a b | a -> b where
    _map :: [b] -> a
    map_ :: [Att24] -> [b] -> a
instance C_Map Ent3 Ent61 where
    _map = Map_3 []
    map_  = Map_3 
instance C_Map Ent4 Ent28 where
    _map = Map_4 []
    map_  = Map_4 
instance C_Map Ent6 Ent28 where
    _map = Map_6 []
    map_  = Map_6 
instance C_Map Ent10 Ent28 where
    _map = Map_10 []
    map_  = Map_10 
instance C_Map Ent12 Ent103 where
    _map = Map_12 []
    map_  = Map_12 
instance C_Map Ent13 Ent103 where
    _map = Map_13 []
    map_  = Map_13 
instance C_Map Ent16 Ent103 where
    _map = Map_16 []
    map_  = Map_16 
instance C_Map Ent17 Ent103 where
    _map = Map_17 []
    map_  = Map_17 
instance C_Map Ent22 Ent28 where
    _map = Map_22 []
    map_  = Map_22 
instance C_Map Ent27 Ent28 where
    _map = Map_27 []
    map_  = Map_27 
instance C_Map Ent29 Ent53 where
    _map = Map_29 []
    map_  = Map_29 
instance C_Map Ent31 Ent53 where
    _map = Map_31 []
    map_  = Map_31 
instance C_Map Ent35 Ent53 where
    _map = Map_35 []
    map_  = Map_35 
instance C_Map Ent37 Ent106 where
    _map = Map_37 []
    map_  = Map_37 
instance C_Map Ent38 Ent106 where
    _map = Map_38 []
    map_  = Map_38 
instance C_Map Ent41 Ent106 where
    _map = Map_41 []
    map_  = Map_41 
instance C_Map Ent42 Ent106 where
    _map = Map_42 []
    map_  = Map_42 
instance C_Map Ent47 Ent53 where
    _map = Map_47 []
    map_  = Map_47 
instance C_Map Ent52 Ent53 where
    _map = Map_52 []
    map_  = Map_52 
instance C_Map Ent56 Ent53 where
    _map = Map_56 []
    map_  = Map_56 
instance C_Map Ent59 Ent28 where
    _map = Map_59 []
    map_  = Map_59 
instance C_Map Ent60 Ent61 where
    _map = Map_60 []
    map_  = Map_60 
instance C_Map Ent62 Ent86 where
    _map = Map_62 []
    map_  = Map_62 
instance C_Map Ent64 Ent86 where
    _map = Map_64 []
    map_  = Map_64 
instance C_Map Ent68 Ent86 where
    _map = Map_68 []
    map_  = Map_68 
instance C_Map Ent70 Ent118 where
    _map = Map_70 []
    map_  = Map_70 
instance C_Map Ent71 Ent118 where
    _map = Map_71 []
    map_  = Map_71 
instance C_Map Ent74 Ent118 where
    _map = Map_74 []
    map_  = Map_74 
instance C_Map Ent75 Ent118 where
    _map = Map_75 []
    map_  = Map_75 
instance C_Map Ent80 Ent86 where
    _map = Map_80 []
    map_  = Map_80 
instance C_Map Ent85 Ent86 where
    _map = Map_85 []
    map_  = Map_85 
instance C_Map Ent89 Ent86 where
    _map = Map_89 []
    map_  = Map_89 
instance C_Map Ent92 Ent61 where
    _map = Map_92 []
    map_  = Map_92 
instance C_Map Ent94 Ent61 where
    _map = Map_94 []
    map_  = Map_94 
instance C_Map Ent97 Ent61 where
    _map = Map_97 []
    map_  = Map_97 
instance C_Map Ent100 Ent115 where
    _map = Map_100 []
    map_  = Map_100 
instance C_Map Ent102 Ent103 where
    _map = Map_102 []
    map_  = Map_102 
instance C_Map Ent105 Ent106 where
    _map = Map_105 []
    map_  = Map_105 
instance C_Map Ent109 Ent106 where
    _map = Map_109 []
    map_  = Map_109 
instance C_Map Ent112 Ent103 where
    _map = Map_112 []
    map_  = Map_112 
instance C_Map Ent113 Ent115 where
    _map = Map_113 []
    map_  = Map_113 
instance C_Map Ent114 Ent115 where
    _map = Map_114 []
    map_  = Map_114 
instance C_Map Ent117 Ent118 where
    _map = Map_117 []
    map_  = Map_117 
instance C_Map Ent121 Ent118 where
    _map = Map_121 []
    map_  = Map_121 
instance C_Map Ent124 Ent115 where
    _map = Map_124 []
    map_  = Map_124 
instance C_Map Ent127 Ent115 where
    _map = Map_127 []
    map_  = Map_127 
instance C_Map Ent128 Ent115 where
    _map = Map_128 []
    map_  = Map_128 
instance C_Map Ent133 Ent61 where
    _map = Map_133 []
    map_  = Map_133 

class C_Area a where
    _area :: a
    area_ :: [Att26] -> a
instance C_Area Ent28 where
    _area = Area_28 []
    area_ = Area_28 
instance C_Area Ent53 where
    _area = Area_53 []
    area_ = Area_53 
instance C_Area Ent61 where
    _area = Area_61 []
    area_ = Area_61 
instance C_Area Ent86 where
    _area = Area_86 []
    area_ = Area_86 
instance C_Area Ent103 where
    _area = Area_103 []
    area_ = Area_103 
instance C_Area Ent106 where
    _area = Area_106 []
    area_ = Area_106 
instance C_Area Ent115 where
    _area = Area_115 []
    area_ = Area_115 
instance C_Area Ent118 where
    _area = Area_118 []
    area_ = Area_118 

class C_Form a b | a -> b where
    _form :: [b] -> a
    form_ :: [Att27] -> [b] -> a
instance C_Form Ent3 Ent98 where
    _form = Form_3 []
    form_  = Form_3 
instance C_Form Ent6 Ent11 where
    _form = Form_6 []
    form_  = Form_6 
instance C_Form Ent7 Ent11 where
    _form = Form_7 []
    form_  = Form_7 
instance C_Form Ent22 Ent11 where
    _form = Form_22 []
    form_  = Form_22 
instance C_Form Ent27 Ent11 where
    _form = Form_27 []
    form_  = Form_27 
instance C_Form Ent28 Ent11 where
    _form = Form_28 []
    form_  = Form_28 
instance C_Form Ent31 Ent36 where
    _form = Form_31 []
    form_  = Form_31 
instance C_Form Ent32 Ent36 where
    _form = Form_32 []
    form_  = Form_32 
instance C_Form Ent47 Ent36 where
    _form = Form_47 []
    form_  = Form_47 
instance C_Form Ent52 Ent36 where
    _form = Form_52 []
    form_  = Form_52 
instance C_Form Ent53 Ent36 where
    _form = Form_53 []
    form_  = Form_53 
instance C_Form Ent61 Ent98 where
    _form = Form_61 []
    form_  = Form_61 
instance C_Form Ent64 Ent69 where
    _form = Form_64 []
    form_  = Form_64 
instance C_Form Ent65 Ent69 where
    _form = Form_65 []
    form_  = Form_65 
instance C_Form Ent80 Ent69 where
    _form = Form_80 []
    form_  = Form_80 
instance C_Form Ent85 Ent69 where
    _form = Form_85 []
    form_  = Form_85 
instance C_Form Ent86 Ent69 where
    _form = Form_86 []
    form_  = Form_86 
instance C_Form Ent93 Ent98 where
    _form = Form_93 []
    form_  = Form_93 
instance C_Form Ent94 Ent98 where
    _form = Form_94 []
    form_  = Form_94 
instance C_Form Ent133 Ent98 where
    _form = Form_133 []
    form_  = Form_133 

class C_Label a b | a -> b where
    _label :: [b] -> a
    label_ :: [Att29] -> [b] -> a
instance C_Label Ent3 Ent62 where
    _label = Label_3 []
    label_  = Label_3 
instance C_Label Ent4 Ent29 where
    _label = Label_4 []
    label_  = Label_4 
instance C_Label Ent6 Ent29 where
    _label = Label_6 []
    label_  = Label_6 
instance C_Label Ent10 Ent29 where
    _label = Label_10 []
    label_  = Label_10 
instance C_Label Ent12 Ent38 where
    _label = Label_12 []
    label_  = Label_12 
instance C_Label Ent13 Ent38 where
    _label = Label_13 []
    label_  = Label_13 
instance C_Label Ent16 Ent38 where
    _label = Label_16 []
    label_  = Label_16 
instance C_Label Ent17 Ent38 where
    _label = Label_17 []
    label_  = Label_17 
instance C_Label Ent22 Ent29 where
    _label = Label_22 []
    label_  = Label_22 
instance C_Label Ent27 Ent29 where
    _label = Label_27 []
    label_  = Label_27 
instance C_Label Ent60 Ent62 where
    _label = Label_60 []
    label_  = Label_60 
instance C_Label Ent94 Ent62 where
    _label = Label_94 []
    label_  = Label_94 
instance C_Label Ent97 Ent62 where
    _label = Label_97 []
    label_  = Label_97 
instance C_Label Ent100 Ent71 where
    _label = Label_100 []
    label_  = Label_100 
instance C_Label Ent102 Ent38 where
    _label = Label_102 []
    label_  = Label_102 
instance C_Label Ent113 Ent71 where
    _label = Label_113 []
    label_  = Label_113 
instance C_Label Ent114 Ent71 where
    _label = Label_114 []
    label_  = Label_114 
instance C_Label Ent127 Ent71 where
    _label = Label_127 []
    label_  = Label_127 
instance C_Label Ent128 Ent71 where
    _label = Label_128 []
    label_  = Label_128 
instance C_Label Ent133 Ent62 where
    _label = Label_133 []
    label_  = Label_133 

class C_Input a where
    _input :: a
    input_ :: [Att30] -> a
instance C_Input Ent3 where
    _input = Input_3 []
    input_ = Input_3 
instance C_Input Ent4 where
    _input = Input_4 []
    input_ = Input_4 
instance C_Input Ent6 where
    _input = Input_6 []
    input_ = Input_6 
instance C_Input Ent10 where
    _input = Input_10 []
    input_ = Input_10 
instance C_Input Ent12 where
    _input = Input_12 []
    input_ = Input_12 
instance C_Input Ent13 where
    _input = Input_13 []
    input_ = Input_13 
instance C_Input Ent16 where
    _input = Input_16 []
    input_ = Input_16 
instance C_Input Ent17 where
    _input = Input_17 []
    input_ = Input_17 
instance C_Input Ent22 where
    _input = Input_22 []
    input_ = Input_22 
instance C_Input Ent27 where
    _input = Input_27 []
    input_ = Input_27 
instance C_Input Ent29 where
    _input = Input_29 []
    input_ = Input_29 
instance C_Input Ent31 where
    _input = Input_31 []
    input_ = Input_31 
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 Ent41 where
    _input = Input_41 []
    input_ = Input_41 
instance C_Input Ent42 where
    _input = Input_42 []
    input_ = Input_42 
instance C_Input Ent47 where
    _input = Input_47 []
    input_ = Input_47 
instance C_Input Ent52 where
    _input = Input_52 []
    input_ = Input_52 
instance C_Input Ent60 where
    _input = Input_60 []
    input_ = Input_60 
instance C_Input Ent62 where
    _input = Input_62 []
    input_ = Input_62 
instance C_Input Ent64 where
    _input = Input_64 []
    input_ = Input_64 
instance C_Input Ent68 where
    _input = Input_68 []
    input_ = Input_68 
instance C_Input Ent70 where
    _input = Input_70 []
    input_ = Input_70 
instance C_Input Ent71 where
    _input = Input_71 []
    input_ = Input_71 
instance C_Input Ent74 where
    _input = Input_74 []
    input_ = Input_74 
instance C_Input Ent75 where
    _input = Input_75 []
    input_ = Input_75 
instance C_Input Ent80 where
    _input = Input_80 []
    input_ = Input_80 
instance C_Input Ent85 where
    _input = Input_85 []
    input_ = Input_85 
instance C_Input Ent94 where
    _input = Input_94 []
    input_ = Input_94 
instance C_Input Ent97 where
    _input = Input_97 []
    input_ = Input_97 
instance C_Input Ent100 where
    _input = Input_100 []
    input_ = Input_100 
instance C_Input Ent102 where
    _input = Input_102 []
    input_ = Input_102 
instance C_Input Ent105 where
    _input = Input_105 []
    input_ = Input_105 
instance C_Input Ent113 where
    _input = Input_113 []
    input_ = Input_113 
instance C_Input Ent114 where
    _input = Input_114 []
    input_ = Input_114 
instance C_Input Ent117 where
    _input = Input_117 []
    input_ = Input_117 
instance C_Input Ent127 where
    _input = Input_127 []
    input_ = Input_127 
instance C_Input Ent128 where
    _input = Input_128 []
    input_ = Input_128 
instance C_Input Ent133 where
    _input = Input_133 []
    input_ = Input_133 

class C_Select a b | a -> b where
    _select :: [b] -> a
    select_ :: [Att31] -> [b] -> a
instance C_Select Ent3 Ent90 where
    _select = Select_3 []
    select_  = Select_3 
instance C_Select Ent4 Ent57 where
    _select = Select_4 []
    select_  = Select_4 
instance C_Select Ent6 Ent57 where
    _select = Select_6 []
    select_  = Select_6 
instance C_Select Ent10 Ent57 where
    _select = Select_10 []
    select_  = Select_10 
instance C_Select Ent12 Ent110 where
    _select = Select_12 []
    select_  = Select_12 
instance C_Select Ent13 Ent110 where
    _select = Select_13 []
    select_  = Select_13 
instance C_Select Ent16 Ent110 where
    _select = Select_16 []
    select_  = Select_16 
instance C_Select Ent17 Ent110 where
    _select = Select_17 []
    select_  = Select_17 
instance C_Select Ent22 Ent57 where
    _select = Select_22 []
    select_  = Select_22 
instance C_Select Ent27 Ent57 where
    _select = Select_27 []
    select_  = Select_27 
instance C_Select Ent29 Ent54 where
    _select = Select_29 []
    select_  = Select_29 
instance C_Select Ent31 Ent54 where
    _select = Select_31 []
    select_  = Select_31 
instance C_Select Ent35 Ent54 where
    _select = Select_35 []
    select_  = Select_35 
instance C_Select Ent37 Ent107 where
    _select = Select_37 []
    select_  = Select_37 
instance C_Select Ent38 Ent107 where
    _select = Select_38 []
    select_  = Select_38 
instance C_Select Ent41 Ent107 where
    _select = Select_41 []
    select_  = Select_41 
instance C_Select Ent42 Ent107 where
    _select = Select_42 []
    select_  = Select_42 
instance C_Select Ent47 Ent54 where
    _select = Select_47 []
    select_  = Select_47 
instance C_Select Ent52 Ent54 where
    _select = Select_52 []
    select_  = Select_52 
instance C_Select Ent60 Ent90 where
    _select = Select_60 []
    select_  = Select_60 
instance C_Select Ent62 Ent87 where
    _select = Select_62 []
    select_  = Select_62 
instance C_Select Ent64 Ent87 where
    _select = Select_64 []
    select_  = Select_64 
instance C_Select Ent68 Ent87 where
    _select = Select_68 []
    select_  = Select_68 
instance C_Select Ent70 Ent119 where
    _select = Select_70 []
    select_  = Select_70 
instance C_Select Ent71 Ent119 where
    _select = Select_71 []
    select_  = Select_71 
instance C_Select Ent74 Ent119 where
    _select = Select_74 []
    select_  = Select_74 
instance C_Select Ent75 Ent119 where
    _select = Select_75 []
    select_  = Select_75 
instance C_Select Ent80 Ent87 where
    _select = Select_80 []
    select_  = Select_80 
instance C_Select Ent85 Ent87 where
    _select = Select_85 []
    select_  = Select_85 
instance C_Select Ent94 Ent90 where
    _select = Select_94 []
    select_  = Select_94 
instance C_Select Ent97 Ent90 where
    _select = Select_97 []
    select_  = Select_97 
instance C_Select Ent100 Ent122 where
    _select = Select_100 []
    select_  = Select_100 
instance C_Select Ent102 Ent110 where
    _select = Select_102 []
    select_  = Select_102 
instance C_Select Ent105 Ent107 where
    _select = Select_105 []
    select_  = Select_105 
instance C_Select Ent113 Ent122 where
    _select = Select_113 []
    select_  = Select_113 
instance C_Select Ent114 Ent122 where
    _select = Select_114 []
    select_  = Select_114 
instance C_Select Ent117 Ent119 where
    _select = Select_117 []
    select_  = Select_117 
instance C_Select Ent127 Ent122 where
    _select = Select_127 []
    select_  = Select_127 
instance C_Select Ent128 Ent122 where
    _select = Select_128 []
    select_  = Select_128 
instance C_Select Ent133 Ent90 where
    _select = Select_133 []
    select_  = Select_133 

class C_Optgroup a b | a -> b where
    _optgroup :: [b] -> a
    optgroup_ :: [Att32] -> [b] -> a
instance C_Optgroup Ent54 Ent55 where
    _optgroup = Optgroup_54 []
    optgroup_  = Optgroup_54 
instance C_Optgroup Ent57 Ent58 where
    _optgroup = Optgroup_57 []
    optgroup_  = Optgroup_57 
instance C_Optgroup Ent87 Ent88 where
    _optgroup = Optgroup_87 []
    optgroup_  = Optgroup_87 
instance C_Optgroup Ent90 Ent91 where
    _optgroup = Optgroup_90 []
    optgroup_  = Optgroup_90 
instance C_Optgroup Ent107 Ent108 where
    _optgroup = Optgroup_107 []
    optgroup_  = Optgroup_107 
instance C_Optgroup Ent110 Ent111 where
    _optgroup = Optgroup_110 []
    optgroup_  = Optgroup_110 
instance C_Optgroup Ent119 Ent120 where
    _optgroup = Optgroup_119 []
    optgroup_  = Optgroup_119 
instance C_Optgroup Ent122 Ent123 where
    _optgroup = Optgroup_122 []
    optgroup_  = Optgroup_122 

class C_Option a b | a -> b where
    _option :: [b] -> a
    option_ :: [Att34] -> [b] -> a
instance C_Option Ent54 Ent30 where
    _option = Option_54 []
    option_  = Option_54 
instance C_Option Ent55 Ent30 where
    _option = Option_55 []
    option_  = Option_55 
instance C_Option Ent57 Ent5 where
    _option = Option_57 []
    option_  = Option_57 
instance C_Option Ent58 Ent5 where
    _option = Option_58 []
    option_  = Option_58 
instance C_Option Ent87 Ent63 where
    _option = Option_87 []
    option_  = Option_87 
instance C_Option Ent88 Ent63 where
    _option = Option_88 []
    option_  = Option_88 
instance C_Option Ent90 Ent2 where
    _option = Option_90 []
    option_  = Option_90 
instance C_Option Ent91 Ent2 where
    _option = Option_91 []
    option_  = Option_91 
instance C_Option Ent107 Ent104 where
    _option = Option_107 []
    option_  = Option_107 
instance C_Option Ent108 Ent104 where
    _option = Option_108 []
    option_  = Option_108 
instance C_Option Ent110 Ent101 where
    _option = Option_110 []
    option_  = Option_110 
instance C_Option Ent111 Ent101 where
    _option = Option_111 []
    option_  = Option_111 
instance C_Option Ent119 Ent116 where
    _option = Option_119 []
    option_  = Option_119 
instance C_Option Ent120 Ent116 where
    _option = Option_120 []
    option_  = Option_120 
instance C_Option Ent122 Ent99 where
    _option = Option_122 []
    option_  = Option_122 
instance C_Option Ent123 Ent99 where
    _option = Option_123 []
    option_  = Option_123 

class C_Textarea a b | a -> b where
    _textarea :: [b] -> a
    textarea_ :: [Att35] -> [b] -> a
instance C_Textarea Ent3 Ent2 where
    _textarea = Textarea_3 []
    textarea_  = Textarea_3 
instance C_Textarea Ent4 Ent5 where
    _textarea = Textarea_4 []
    textarea_  = Textarea_4 
instance C_Textarea Ent6 Ent5 where
    _textarea = Textarea_6 []
    textarea_  = Textarea_6 
instance C_Textarea Ent10 Ent5 where
    _textarea = Textarea_10 []
    textarea_  = Textarea_10 
instance C_Textarea Ent12 Ent101 where
    _textarea = Textarea_12 []
    textarea_  = Textarea_12 
instance C_Textarea Ent13 Ent101 where
    _textarea = Textarea_13 []
    textarea_  = Textarea_13 
instance C_Textarea Ent16 Ent101 where
    _textarea = Textarea_16 []
    textarea_  = Textarea_16 
instance C_Textarea Ent17 Ent101 where
    _textarea = Textarea_17 []
    textarea_  = Textarea_17 
instance C_Textarea Ent22 Ent5 where
    _textarea = Textarea_22 []
    textarea_  = Textarea_22 
instance C_Textarea Ent27 Ent5 where
    _textarea = Textarea_27 []
    textarea_  = Textarea_27 
instance C_Textarea Ent29 Ent30 where
    _textarea = Textarea_29 []
    textarea_  = Textarea_29 
instance C_Textarea Ent31 Ent30 where
    _textarea = Textarea_31 []
    textarea_  = Textarea_31 
instance C_Textarea Ent35 Ent30 where
    _textarea = Textarea_35 []
    textarea_  = Textarea_35 
instance C_Textarea Ent37 Ent104 where
    _textarea = Textarea_37 []
    textarea_  = Textarea_37 
instance C_Textarea Ent38 Ent104 where
    _textarea = Textarea_38 []
    textarea_  = Textarea_38 
instance C_Textarea Ent41 Ent104 where
    _textarea = Textarea_41 []
    textarea_  = Textarea_41 
instance C_Textarea Ent42 Ent104 where
    _textarea = Textarea_42 []
    textarea_  = Textarea_42 
instance C_Textarea Ent47 Ent30 where
    _textarea = Textarea_47 []
    textarea_  = Textarea_47 
instance C_Textarea Ent52 Ent30 where
    _textarea = Textarea_52 []
    textarea_  = Textarea_52 
instance C_Textarea Ent60 Ent2 where
    _textarea = Textarea_60 []
    textarea_  = Textarea_60 
instance C_Textarea Ent62 Ent63 where
    _textarea = Textarea_62 []
    textarea_  = Textarea_62 
instance C_Textarea Ent64 Ent63 where
    _textarea = Textarea_64 []
    textarea_  = Textarea_64 
instance C_Textarea Ent68 Ent63 where
    _textarea = Textarea_68 []
    textarea_  = Textarea_68 
instance C_Textarea Ent70 Ent116 where
    _textarea = Textarea_70 []
    textarea_  = Textarea_70 
instance C_Textarea Ent71 Ent116 where
    _textarea = Textarea_71 []
    textarea_  = Textarea_71 
instance C_Textarea Ent74 Ent116 where
    _textarea = Textarea_74 []
    textarea_  = Textarea_74 
instance C_Textarea Ent75 Ent116 where
    _textarea = Textarea_75 []
    textarea_  = Textarea_75 
instance C_Textarea Ent80 Ent63 where
    _textarea = Textarea_80 []
    textarea_  = Textarea_80 
instance C_Textarea Ent85 Ent63 where
    _textarea = Textarea_85 []
    textarea_  = Textarea_85 
instance C_Textarea Ent94 Ent2 where
    _textarea = Textarea_94 []
    textarea_  = Textarea_94 
instance C_Textarea Ent97 Ent2 where
    _textarea = Textarea_97 []
    textarea_  = Textarea_97 
instance C_Textarea Ent100 Ent99 where
    _textarea = Textarea_100 []
    textarea_  = Textarea_100 
instance C_Textarea Ent102 Ent101 where
    _textarea = Textarea_102 []
    textarea_  = Textarea_102 
instance C_Textarea Ent105 Ent104 where
    _textarea = Textarea_105 []
    textarea_  = Textarea_105 
instance C_Textarea Ent113 Ent99 where
    _textarea = Textarea_113 []
    textarea_  = Textarea_113 
instance C_Textarea Ent114 Ent99 where
    _textarea = Textarea_114 []
    textarea_  = Textarea_114 
instance C_Textarea Ent117 Ent116 where
    _textarea = Textarea_117 []
    textarea_  = Textarea_117 
instance C_Textarea Ent127 Ent99 where
    _textarea = Textarea_127 []
    textarea_  = Textarea_127 
instance C_Textarea Ent128 Ent99 where
    _textarea = Textarea_128 []
    textarea_  = Textarea_128 
instance C_Textarea Ent133 Ent2 where
    _textarea = Textarea_133 []
    textarea_  = Textarea_133 

class C_Fieldset a b | a -> b where
    _fieldset :: [b] -> a
    fieldset_ :: [Att11] -> [b] -> a
instance C_Fieldset Ent3 Ent133 where
    _fieldset = Fieldset_3 []
    fieldset_  = Fieldset_3 
instance C_Fieldset Ent6 Ent22 where
    _fieldset = Fieldset_6 []
    fieldset_  = Fieldset_6 
instance C_Fieldset Ent7 Ent22 where
    _fieldset = Fieldset_7 []
    fieldset_  = Fieldset_7 
instance C_Fieldset Ent11 Ent17 where
    _fieldset = Fieldset_11 []
    fieldset_  = Fieldset_11 
instance C_Fieldset Ent12 Ent17 where
    _fieldset = Fieldset_12 []
    fieldset_  = Fieldset_12 
instance C_Fieldset Ent17 Ent17 where
    _fieldset = Fieldset_17 []
    fieldset_  = Fieldset_17 
instance C_Fieldset Ent22 Ent22 where
    _fieldset = Fieldset_22 []
    fieldset_  = Fieldset_22 
instance C_Fieldset Ent27 Ent22 where
    _fieldset = Fieldset_27 []
    fieldset_  = Fieldset_27 
instance C_Fieldset Ent28 Ent22 where
    _fieldset = Fieldset_28 []
    fieldset_  = Fieldset_28 
instance C_Fieldset Ent31 Ent47 where
    _fieldset = Fieldset_31 []
    fieldset_  = Fieldset_31 
instance C_Fieldset Ent32 Ent47 where
    _fieldset = Fieldset_32 []
    fieldset_  = Fieldset_32 
instance C_Fieldset Ent36 Ent42 where
    _fieldset = Fieldset_36 []
    fieldset_  = Fieldset_36 
instance C_Fieldset Ent37 Ent42 where
    _fieldset = Fieldset_37 []
    fieldset_  = Fieldset_37 
instance C_Fieldset Ent42 Ent42 where
    _fieldset = Fieldset_42 []
    fieldset_  = Fieldset_42 
instance C_Fieldset Ent47 Ent47 where
    _fieldset = Fieldset_47 []
    fieldset_  = Fieldset_47 
instance C_Fieldset Ent52 Ent47 where
    _fieldset = Fieldset_52 []
    fieldset_  = Fieldset_52 
instance C_Fieldset Ent53 Ent47 where
    _fieldset = Fieldset_53 []
    fieldset_  = Fieldset_53 
instance C_Fieldset Ent61 Ent133 where
    _fieldset = Fieldset_61 []
    fieldset_  = Fieldset_61 
instance C_Fieldset Ent64 Ent80 where
    _fieldset = Fieldset_64 []
    fieldset_  = Fieldset_64 
instance C_Fieldset Ent65 Ent80 where
    _fieldset = Fieldset_65 []
    fieldset_  = Fieldset_65 
instance C_Fieldset Ent69 Ent75 where
    _fieldset = Fieldset_69 []
    fieldset_  = Fieldset_69 
instance C_Fieldset Ent70 Ent75 where
    _fieldset = Fieldset_70 []
    fieldset_  = Fieldset_70 
instance C_Fieldset Ent75 Ent75 where
    _fieldset = Fieldset_75 []
    fieldset_  = Fieldset_75 
instance C_Fieldset Ent80 Ent80 where
    _fieldset = Fieldset_80 []
    fieldset_  = Fieldset_80 
instance C_Fieldset Ent85 Ent80 where
    _fieldset = Fieldset_85 []
    fieldset_  = Fieldset_85 
instance C_Fieldset Ent86 Ent80 where
    _fieldset = Fieldset_86 []
    fieldset_  = Fieldset_86 
instance C_Fieldset Ent93 Ent133 where
    _fieldset = Fieldset_93 []
    fieldset_  = Fieldset_93 
instance C_Fieldset Ent94 Ent133 where
    _fieldset = Fieldset_94 []
    fieldset_  = Fieldset_94 
instance C_Fieldset Ent98 Ent128 where
    _fieldset = Fieldset_98 []
    fieldset_  = Fieldset_98 
instance C_Fieldset Ent100 Ent128 where
    _fieldset = Fieldset_100 []
    fieldset_  = Fieldset_100 
instance C_Fieldset Ent102 Ent17 where
    _fieldset = Fieldset_102 []
    fieldset_  = Fieldset_102 
instance C_Fieldset Ent103 Ent17 where
    _fieldset = Fieldset_103 []
    fieldset_  = Fieldset_103 
instance C_Fieldset Ent105 Ent42 where
    _fieldset = Fieldset_105 []
    fieldset_  = Fieldset_105 
instance C_Fieldset Ent106 Ent42 where
    _fieldset = Fieldset_106 []
    fieldset_  = Fieldset_106 
instance C_Fieldset Ent114 Ent128 where
    _fieldset = Fieldset_114 []
    fieldset_  = Fieldset_114 
instance C_Fieldset Ent115 Ent128 where
    _fieldset = Fieldset_115 []
    fieldset_  = Fieldset_115 
instance C_Fieldset Ent117 Ent75 where
    _fieldset = Fieldset_117 []
    fieldset_  = Fieldset_117 
instance C_Fieldset Ent118 Ent75 where
    _fieldset = Fieldset_118 []
    fieldset_  = Fieldset_118 
instance C_Fieldset Ent128 Ent128 where
    _fieldset = Fieldset_128 []
    fieldset_  = Fieldset_128 
instance C_Fieldset Ent133 Ent133 where
    _fieldset = Fieldset_133 []
    fieldset_  = Fieldset_133 

class C_Legend a b | a -> b where
    _legend :: [b] -> a
    legend_ :: [Att38] -> [b] -> a
instance C_Legend Ent17 Ent13 where
    _legend = Legend_17 []
    legend_  = Legend_17 
instance C_Legend Ent22 Ent4 where
    _legend = Legend_22 []
    legend_  = Legend_22 
instance C_Legend Ent42 Ent38 where
    _legend = Legend_42 []
    legend_  = Legend_42 
instance C_Legend Ent47 Ent29 where
    _legend = Legend_47 []
    legend_  = Legend_47 
instance C_Legend Ent75 Ent71 where
    _legend = Legend_75 []
    legend_  = Legend_75 
instance C_Legend Ent80 Ent62 where
    _legend = Legend_80 []
    legend_  = Legend_80 
instance C_Legend Ent128 Ent113 where
    _legend = Legend_128 []
    legend_  = Legend_128 
instance C_Legend Ent133 Ent60 where
    _legend = Legend_133 []
    legend_  = Legend_133 

class C_Button a b | a -> b where
    _button :: [b] -> a
    button_ :: [Att39] -> [b] -> a
instance C_Button Ent3 Ent92 where
    _button = Button_3 []
    button_  = Button_3 
instance C_Button Ent4 Ent59 where
    _button = Button_4 []
    button_  = Button_4 
instance C_Button Ent6 Ent59 where
    _button = Button_6 []
    button_  = Button_6 
instance C_Button Ent10 Ent59 where
    _button = Button_10 []
    button_  = Button_10 
instance C_Button Ent12 Ent112 where
    _button = Button_12 []
    button_  = Button_12 
instance C_Button Ent13 Ent112 where
    _button = Button_13 []
    button_  = Button_13 
instance C_Button Ent16 Ent112 where
    _button = Button_16 []
    button_  = Button_16 
instance C_Button Ent17 Ent112 where
    _button = Button_17 []
    button_  = Button_17 
instance C_Button Ent22 Ent59 where
    _button = Button_22 []
    button_  = Button_22 
instance C_Button Ent27 Ent59 where
    _button = Button_27 []
    button_  = Button_27 
instance C_Button Ent29 Ent56 where
    _button = Button_29 []
    button_  = Button_29 
instance C_Button Ent31 Ent56 where
    _button = Button_31 []
    button_  = Button_31 
instance C_Button Ent35 Ent56 where
    _button = Button_35 []
    button_  = Button_35 
instance C_Button Ent37 Ent109 where
    _button = Button_37 []
    button_  = Button_37 
instance C_Button Ent38 Ent109 where
    _button = Button_38 []
    button_  = Button_38 
instance C_Button Ent41 Ent109 where
    _button = Button_41 []
    button_  = Button_41 
instance C_Button Ent42 Ent109 where
    _button = Button_42 []
    button_  = Button_42 
instance C_Button Ent47 Ent56 where
    _button = Button_47 []
    button_  = Button_47 
instance C_Button Ent52 Ent56 where
    _button = Button_52 []
    button_  = Button_52 
instance C_Button Ent60 Ent92 where
    _button = Button_60 []
    button_  = Button_60 
instance C_Button Ent62 Ent89 where
    _button = Button_62 []
    button_  = Button_62 
instance C_Button Ent64 Ent89 where
    _button = Button_64 []
    button_  = Button_64 
instance C_Button Ent68 Ent89 where
    _button = Button_68 []
    button_  = Button_68 
instance C_Button Ent70 Ent121 where
    _button = Button_70 []
    button_  = Button_70 
instance C_Button Ent71 Ent121 where
    _button = Button_71 []
    button_  = Button_71 
instance C_Button Ent74 Ent121 where
    _button = Button_74 []
    button_  = Button_74 
instance C_Button Ent75 Ent121 where
    _button = Button_75 []
    button_  = Button_75 
instance C_Button Ent80 Ent89 where
    _button = Button_80 []
    button_  = Button_80 
instance C_Button Ent85 Ent89 where
    _button = Button_85 []
    button_  = Button_85 
instance C_Button Ent94 Ent92 where
    _button = Button_94 []
    button_  = Button_94 
instance C_Button Ent97 Ent92 where
    _button = Button_97 []
    button_  = Button_97 
instance C_Button Ent100 Ent124 where
    _button = Button_100 []
    button_  = Button_100 
instance C_Button Ent102 Ent112 where
    _button = Button_102 []
    button_  = Button_102 
instance C_Button Ent105 Ent109 where
    _button = Button_105 []
    button_  = Button_105 
instance C_Button Ent113 Ent124 where
    _button = Button_113 []
    button_  = Button_113 
instance C_Button Ent114 Ent124 where
    _button = Button_114 []
    button_  = Button_114 
instance C_Button Ent117 Ent121 where
    _button = Button_117 []
    button_  = Button_117 
instance C_Button Ent127 Ent124 where
    _button = Button_127 []
    button_  = Button_127 
instance C_Button Ent128 Ent124 where
    _button = Button_128 []
    button_  = Button_128 
instance C_Button Ent133 Ent92 where
    _button = Button_133 []
    button_  = Button_133 

class C_Table a b | a -> b where
    _table :: [b] -> a
    table_ :: [Att40] -> [b] -> a
instance C_Table Ent3 Ent134 where
    _table = Table_3 []
    table_  = Table_3 
instance C_Table Ent6 Ent23 where
    _table = Table_6 []
    table_  = Table_6 
instance C_Table Ent7 Ent23 where
    _table = Table_7 []
    table_  = Table_7 
instance C_Table Ent11 Ent18 where
    _table = Table_11 []
    table_  = Table_11 
instance C_Table Ent12 Ent18 where
    _table = Table_12 []
    table_  = Table_12 
instance C_Table Ent17 Ent18 where
    _table = Table_17 []
    table_  = Table_17 
instance C_Table Ent22 Ent23 where
    _table = Table_22 []
    table_  = Table_22 
instance C_Table Ent27 Ent23 where
    _table = Table_27 []
    table_  = Table_27 
instance C_Table Ent28 Ent23 where
    _table = Table_28 []
    table_  = Table_28 
instance C_Table Ent31 Ent48 where
    _table = Table_31 []
    table_  = Table_31 
instance C_Table Ent32 Ent48 where
    _table = Table_32 []
    table_  = Table_32 
instance C_Table Ent36 Ent43 where
    _table = Table_36 []
    table_  = Table_36 
instance C_Table Ent37 Ent43 where
    _table = Table_37 []
    table_  = Table_37 
instance C_Table Ent42 Ent43 where
    _table = Table_42 []
    table_  = Table_42 
instance C_Table Ent47 Ent48 where
    _table = Table_47 []
    table_  = Table_47 
instance C_Table Ent52 Ent48 where
    _table = Table_52 []
    table_  = Table_52 
instance C_Table Ent53 Ent48 where
    _table = Table_53 []
    table_  = Table_53 
instance C_Table Ent56 Ent48 where
    _table = Table_56 []
    table_  = Table_56 
instance C_Table Ent59 Ent23 where
    _table = Table_59 []
    table_  = Table_59 
instance C_Table Ent61 Ent134 where
    _table = Table_61 []
    table_  = Table_61 
instance C_Table Ent64 Ent81 where
    _table = Table_64 []
    table_  = Table_64 
instance C_Table Ent65 Ent81 where
    _table = Table_65 []
    table_  = Table_65 
instance C_Table Ent69 Ent76 where
    _table = Table_69 []
    table_  = Table_69 
instance C_Table Ent70 Ent76 where
    _table = Table_70 []
    table_  = Table_70 
instance C_Table Ent75 Ent76 where
    _table = Table_75 []
    table_  = Table_75 
instance C_Table Ent80 Ent81 where
    _table = Table_80 []
    table_  = Table_80 
instance C_Table Ent85 Ent81 where
    _table = Table_85 []
    table_  = Table_85 
instance C_Table Ent86 Ent81 where
    _table = Table_86 []
    table_  = Table_86 
instance C_Table Ent89 Ent81 where
    _table = Table_89 []
    table_  = Table_89 
instance C_Table Ent92 Ent134 where
    _table = Table_92 []
    table_  = Table_92 
instance C_Table Ent93 Ent134 where
    _table = Table_93 []
    table_  = Table_93 
instance C_Table Ent94 Ent134 where
    _table = Table_94 []
    table_  = Table_94 
instance C_Table Ent98 Ent129 where
    _table = Table_98 []
    table_  = Table_98 
instance C_Table Ent100 Ent129 where
    _table = Table_100 []
    table_  = Table_100 
instance C_Table Ent102 Ent18 where
    _table = Table_102 []
    table_  = Table_102 
instance C_Table Ent103 Ent18 where
    _table = Table_103 []
    table_  = Table_103 
instance C_Table Ent105 Ent43 where
    _table = Table_105 []
    table_  = Table_105 
instance C_Table Ent106 Ent43 where
    _table = Table_106 []
    table_  = Table_106 
instance C_Table Ent109 Ent43 where
    _table = Table_109 []
    table_  = Table_109 
instance C_Table Ent112 Ent18 where
    _table = Table_112 []
    table_  = Table_112 
instance C_Table Ent114 Ent129 where
    _table = Table_114 []
    table_  = Table_114 
instance C_Table Ent115 Ent129 where
    _table = Table_115 []
    table_  = Table_115 
instance C_Table Ent117 Ent76 where
    _table = Table_117 []
    table_  = Table_117 
instance C_Table Ent118 Ent76 where
    _table = Table_118 []
    table_  = Table_118 
instance C_Table Ent121 Ent76 where
    _table = Table_121 []
    table_  = Table_121 
instance C_Table Ent124 Ent129 where
    _table = Table_124 []
    table_  = Table_124 
instance C_Table Ent128 Ent129 where
    _table = Table_128 []
    table_  = Table_128 
instance C_Table Ent133 Ent134 where
    _table = Table_133 []
    table_  = Table_133 

class C_Caption a b | a -> b where
    _caption :: [b] -> a
    caption_ :: [Att11] -> [b] -> a
instance C_Caption Ent18 Ent13 where
    _caption = Caption_18 []
    caption_  = Caption_18 
instance C_Caption Ent23 Ent4 where
    _caption = Caption_23 []
    caption_  = Caption_23 
instance C_Caption Ent43 Ent38 where
    _caption = Caption_43 []
    caption_  = Caption_43 
instance C_Caption Ent48 Ent29 where
    _caption = Caption_48 []
    caption_  = Caption_48 
instance C_Caption Ent76 Ent71 where
    _caption = Caption_76 []
    caption_  = Caption_76 
instance C_Caption Ent81 Ent62 where
    _caption = Caption_81 []
    caption_  = Caption_81 
instance C_Caption Ent129 Ent113 where
    _caption = Caption_129 []
    caption_  = Caption_129 
instance C_Caption Ent134 Ent60 where
    _caption = Caption_134 []
    caption_  = Caption_134 

class C_Thead a b | a -> b where
    _thead :: [b] -> a
    thead_ :: [Att41] -> [b] -> a
instance C_Thead Ent18 Ent19 where
    _thead = Thead_18 []
    thead_  = Thead_18 
instance C_Thead Ent23 Ent24 where
    _thead = Thead_23 []
    thead_  = Thead_23 
instance C_Thead Ent43 Ent44 where
    _thead = Thead_43 []
    thead_  = Thead_43 
instance C_Thead Ent48 Ent49 where
    _thead = Thead_48 []
    thead_  = Thead_48 
instance C_Thead Ent76 Ent77 where
    _thead = Thead_76 []
    thead_  = Thead_76 
instance C_Thead Ent81 Ent82 where
    _thead = Thead_81 []
    thead_  = Thead_81 
instance C_Thead Ent129 Ent130 where
    _thead = Thead_129 []
    thead_  = Thead_129 
instance C_Thead Ent134 Ent135 where
    _thead = Thead_134 []
    thead_  = Thead_134 

class C_Tfoot a b | a -> b where
    _tfoot :: [b] -> a
    tfoot_ :: [Att41] -> [b] -> a
instance C_Tfoot Ent18 Ent19 where
    _tfoot = Tfoot_18 []
    tfoot_  = Tfoot_18 
instance C_Tfoot Ent23 Ent24 where
    _tfoot = Tfoot_23 []
    tfoot_  = Tfoot_23 
instance C_Tfoot Ent43 Ent44 where
    _tfoot = Tfoot_43 []
    tfoot_  = Tfoot_43 
instance C_Tfoot Ent48 Ent49 where
    _tfoot = Tfoot_48 []
    tfoot_  = Tfoot_48 
instance C_Tfoot Ent76 Ent77 where
    _tfoot = Tfoot_76 []
    tfoot_  = Tfoot_76 
instance C_Tfoot Ent81 Ent82 where
    _tfoot = Tfoot_81 []
    tfoot_  = Tfoot_81 
instance C_Tfoot Ent129 Ent130 where
    _tfoot = Tfoot_129 []
    tfoot_  = Tfoot_129 
instance C_Tfoot Ent134 Ent135 where
    _tfoot = Tfoot_134 []
    tfoot_  = Tfoot_134 

class C_Tbody a b | a -> b where
    _tbody :: [b] -> a
    tbody_ :: [Att41] -> [b] -> a
instance C_Tbody Ent18 Ent19 where
    _tbody = Tbody_18 []
    tbody_  = Tbody_18 
instance C_Tbody Ent23 Ent24 where
    _tbody = Tbody_23 []
    tbody_  = Tbody_23 
instance C_Tbody Ent43 Ent44 where
    _tbody = Tbody_43 []
    tbody_  = Tbody_43 
instance C_Tbody Ent48 Ent49 where
    _tbody = Tbody_48 []
    tbody_  = Tbody_48 
instance C_Tbody Ent76 Ent77 where
    _tbody = Tbody_76 []
    tbody_  = Tbody_76 
instance C_Tbody Ent81 Ent82 where
    _tbody = Tbody_81 []
    tbody_  = Tbody_81 
instance C_Tbody Ent129 Ent130 where
    _tbody = Tbody_129 []
    tbody_  = Tbody_129 
instance C_Tbody Ent134 Ent135 where
    _tbody = Tbody_134 []
    tbody_  = Tbody_134 

class C_Colgroup a b | a -> b where
    _colgroup :: [b] -> a
    colgroup_ :: [Att42] -> [b] -> a
instance C_Colgroup Ent18 Ent20 where
    _colgroup = Colgroup_18 []
    colgroup_  = Colgroup_18 
instance C_Colgroup Ent23 Ent25 where
    _colgroup = Colgroup_23 []
    colgroup_  = Colgroup_23 
instance C_Colgroup Ent43 Ent45 where
    _colgroup = Colgroup_43 []
    colgroup_  = Colgroup_43 
instance C_Colgroup Ent48 Ent50 where
    _colgroup = Colgroup_48 []
    colgroup_  = Colgroup_48 
instance C_Colgroup Ent76 Ent78 where
    _colgroup = Colgroup_76 []
    colgroup_  = Colgroup_76 
instance C_Colgroup Ent81 Ent83 where
    _colgroup = Colgroup_81 []
    colgroup_  = Colgroup_81 
instance C_Colgroup Ent129 Ent131 where
    _colgroup = Colgroup_129 []
    colgroup_  = Colgroup_129 
instance C_Colgroup Ent134 Ent136 where
    _colgroup = Colgroup_134 []
    colgroup_  = Colgroup_134 

class C_Col a where
    _col :: a
    col_ :: [Att42] -> a
instance C_Col Ent18 where
    _col = Col_18 []
    col_ = Col_18 
instance C_Col Ent20 where
    _col = Col_20 []
    col_ = Col_20 
instance C_Col Ent23 where
    _col = Col_23 []
    col_ = Col_23 
instance C_Col Ent25 where
    _col = Col_25 []
    col_ = Col_25 
instance C_Col Ent43 where
    _col = Col_43 []
    col_ = Col_43 
instance C_Col Ent45 where
    _col = Col_45 []
    col_ = Col_45 
instance C_Col Ent48 where
    _col = Col_48 []
    col_ = Col_48 
instance C_Col Ent50 where
    _col = Col_50 []
    col_ = Col_50 
instance C_Col Ent76 where
    _col = Col_76 []
    col_ = Col_76 
instance C_Col Ent78 where
    _col = Col_78 []
    col_ = Col_78 
instance C_Col Ent81 where
    _col = Col_81 []
    col_ = Col_81 
instance C_Col Ent83 where
    _col = Col_83 []
    col_ = Col_83 
instance C_Col Ent129 where
    _col = Col_129 []
    col_ = Col_129 
instance C_Col Ent131 where
    _col = Col_131 []
    col_ = Col_131 
instance C_Col Ent134 where
    _col = Col_134 []
    col_ = Col_134 
instance C_Col Ent136 where
    _col = Col_136 []
    col_ = Col_136 

class C_Tr a b | a -> b where
    _tr :: [b] -> a
    tr_ :: [Att41] -> [b] -> a
instance C_Tr Ent18 Ent21 where
    _tr = Tr_18 []
    tr_  = Tr_18 
instance C_Tr Ent19 Ent21 where
    _tr = Tr_19 []
    tr_  = Tr_19 
instance C_Tr Ent23 Ent26 where
    _tr = Tr_23 []
    tr_  = Tr_23 
instance C_Tr Ent24 Ent26 where
    _tr = Tr_24 []
    tr_  = Tr_24 
instance C_Tr Ent43 Ent46 where
    _tr = Tr_43 []
    tr_  = Tr_43 
instance C_Tr Ent44 Ent46 where
    _tr = Tr_44 []
    tr_  = Tr_44 
instance C_Tr Ent48 Ent51 where
    _tr = Tr_48 []
    tr_  = Tr_48 
instance C_Tr Ent49 Ent51 where
    _tr = Tr_49 []
    tr_  = Tr_49 
instance C_Tr Ent76 Ent79 where
    _tr = Tr_76 []
    tr_  = Tr_76 
instance C_Tr Ent77 Ent79 where
    _tr = Tr_77 []
    tr_  = Tr_77 
instance C_Tr Ent81 Ent84 where
    _tr = Tr_81 []
    tr_  = Tr_81 
instance C_Tr Ent82 Ent84 where
    _tr = Tr_82 []
    tr_  = Tr_82 
instance C_Tr Ent129 Ent132 where
    _tr = Tr_129 []
    tr_  = Tr_129 
instance C_Tr Ent130 Ent132 where
    _tr = Tr_130 []
    tr_  = Tr_130 
instance C_Tr Ent134 Ent137 where
    _tr = Tr_134 []
    tr_  = Tr_134 
instance C_Tr Ent135 Ent137 where
    _tr = Tr_135 []
    tr_  = Tr_135 

class C_Th a b | a -> b where
    _th :: [b] -> a
    th_ :: [Att43] -> [b] -> a
instance C_Th Ent21 Ent12 where
    _th = Th_21 []
    th_  = Th_21 
instance C_Th Ent26 Ent6 where
    _th = Th_26 []
    th_  = Th_26 
instance C_Th Ent46 Ent37 where
    _th = Th_46 []
    th_  = Th_46 
instance C_Th Ent51 Ent31 where
    _th = Th_51 []
    th_  = Th_51 
instance C_Th Ent79 Ent70 where
    _th = Th_79 []
    th_  = Th_79 
instance C_Th Ent84 Ent64 where
    _th = Th_84 []
    th_  = Th_84 
instance C_Th Ent132 Ent100 where
    _th = Th_132 []
    th_  = Th_132 
instance C_Th Ent137 Ent94 where
    _th = Th_137 []
    th_  = Th_137 

class C_Td a b | a -> b where
    _td :: [b] -> a
    td_ :: [Att43] -> [b] -> a
instance C_Td Ent21 Ent12 where
    _td = Td_21 []
    td_  = Td_21 
instance C_Td Ent26 Ent6 where
    _td = Td_26 []
    td_  = Td_26 
instance C_Td Ent46 Ent37 where
    _td = Td_46 []
    td_  = Td_46 
instance C_Td Ent51 Ent31 where
    _td = Td_51 []
    td_  = Td_51 
instance C_Td Ent79 Ent70 where
    _td = Td_79 []
    td_  = Td_79 
instance C_Td Ent84 Ent64 where
    _td = Td_84 []
    td_  = Td_84 
instance C_Td Ent132 Ent100 where
    _td = Td_132 []
    td_  = Td_132 
instance C_Td Ent137 Ent94 where
    _td = Td_137 []
    td_  = Td_137 

class C_PCDATA a where
    pcdata :: String -> a
    pcdata_bs :: B.ByteString -> a
    ce_quot :: a
    ce_amp :: a
    ce_lt :: a
    ce_gt :: a
    ce_copy :: a
    ce_reg :: a
    ce_nbsp :: a
instance C_PCDATA Ent2 where
    pcdata s = PCDATA_2 [] (s2b_escape s)
    pcdata_bs = PCDATA_2 []
    ce_quot = PCDATA_2 [] (s2b "&quot;")
    ce_amp = PCDATA_2 [] (s2b "&amp;")
    ce_lt = PCDATA_2 [] (s2b "&lt;")
    ce_gt = PCDATA_2 [] (s2b "&gt;")
    ce_copy = PCDATA_2 [] (s2b "&copy;")
    ce_reg = PCDATA_2 [] (s2b "&reg;")
    ce_nbsp = PCDATA_2 [] (s2b "&nbsp;")
instance C_PCDATA Ent3 where
    pcdata s = PCDATA_3 [] (s2b_escape s)
    pcdata_bs = PCDATA_3 []
    ce_quot = PCDATA_3 [] (s2b "&quot;")
    ce_amp = PCDATA_3 [] (s2b "&amp;")
    ce_lt = PCDATA_3 [] (s2b "&lt;")
    ce_gt = PCDATA_3 [] (s2b "&gt;")
    ce_copy = PCDATA_3 [] (s2b "&copy;")
    ce_reg = PCDATA_3 [] (s2b "&reg;")
    ce_nbsp = PCDATA_3 [] (s2b "&nbsp;")
instance C_PCDATA Ent4 where
    pcdata s = PCDATA_4 [] (s2b_escape s)
    pcdata_bs = PCDATA_4 []
    ce_quot = PCDATA_4 [] (s2b "&quot;")
    ce_amp = PCDATA_4 [] (s2b "&amp;")
    ce_lt = PCDATA_4 [] (s2b "&lt;")
    ce_gt = PCDATA_4 [] (s2b "&gt;")
    ce_copy = PCDATA_4 [] (s2b "&copy;")
    ce_reg = PCDATA_4 [] (s2b "&reg;")
    ce_nbsp = PCDATA_4 [] (s2b "&nbsp;")
instance C_PCDATA Ent5 where
    pcdata s = PCDATA_5 [] (s2b_escape s)
    pcdata_bs = PCDATA_5 []
    ce_quot = PCDATA_5 [] (s2b "&quot;")
    ce_amp = PCDATA_5 [] (s2b "&amp;")
    ce_lt = PCDATA_5 [] (s2b "&lt;")
    ce_gt = PCDATA_5 [] (s2b "&gt;")
    ce_copy = PCDATA_5 [] (s2b "&copy;")
    ce_reg = PCDATA_5 [] (s2b "&reg;")
    ce_nbsp = PCDATA_5 [] (s2b "&nbsp;")
instance C_PCDATA Ent6 where
    pcdata s = PCDATA_6 [] (s2b_escape s)
    pcdata_bs = PCDATA_6 []
    ce_quot = PCDATA_6 [] (s2b "&quot;")
    ce_amp = PCDATA_6 [] (s2b "&amp;")
    ce_lt = PCDATA_6 [] (s2b "&lt;")
    ce_gt = PCDATA_6 [] (s2b "&gt;")
    ce_copy = PCDATA_6 [] (s2b "&copy;")
    ce_reg = PCDATA_6 [] (s2b "&reg;")
    ce_nbsp = PCDATA_6 [] (s2b "&nbsp;")
instance C_PCDATA Ent10 where
    pcdata s = PCDATA_10 [] (s2b_escape s)
    pcdata_bs = PCDATA_10 []
    ce_quot = PCDATA_10 [] (s2b "&quot;")
    ce_amp = PCDATA_10 [] (s2b "&amp;")
    ce_lt = PCDATA_10 [] (s2b "&lt;")
    ce_gt = PCDATA_10 [] (s2b "&gt;")
    ce_copy = PCDATA_10 [] (s2b "&copy;")
    ce_reg = PCDATA_10 [] (s2b "&reg;")
    ce_nbsp = PCDATA_10 [] (s2b "&nbsp;")
instance C_PCDATA Ent12 where
    pcdata s = PCDATA_12 [] (s2b_escape s)
    pcdata_bs = PCDATA_12 []
    ce_quot = PCDATA_12 [] (s2b "&quot;")
    ce_amp = PCDATA_12 [] (s2b "&amp;")
    ce_lt = PCDATA_12 [] (s2b "&lt;")
    ce_gt = PCDATA_12 [] (s2b "&gt;")
    ce_copy = PCDATA_12 [] (s2b "&copy;")
    ce_reg = PCDATA_12 [] (s2b "&reg;")
    ce_nbsp = PCDATA_12 [] (s2b "&nbsp;")
instance C_PCDATA Ent13 where
    pcdata s = PCDATA_13 [] (s2b_escape s)
    pcdata_bs = PCDATA_13 []
    ce_quot = PCDATA_13 [] (s2b "&quot;")
    ce_amp = PCDATA_13 [] (s2b "&amp;")
    ce_lt = PCDATA_13 [] (s2b "&lt;")
    ce_gt = PCDATA_13 [] (s2b "&gt;")
    ce_copy = PCDATA_13 [] (s2b "&copy;")
    ce_reg = PCDATA_13 [] (s2b "&reg;")
    ce_nbsp = PCDATA_13 [] (s2b "&nbsp;")
instance C_PCDATA Ent16 where
    pcdata s = PCDATA_16 [] (s2b_escape s)
    pcdata_bs = PCDATA_16 []
    ce_quot = PCDATA_16 [] (s2b "&quot;")
    ce_amp = PCDATA_16 [] (s2b "&amp;")
    ce_lt = PCDATA_16 [] (s2b "&lt;")
    ce_gt = PCDATA_16 [] (s2b "&gt;")
    ce_copy = PCDATA_16 [] (s2b "&copy;")
    ce_reg = PCDATA_16 [] (s2b "&reg;")
    ce_nbsp = PCDATA_16 [] (s2b "&nbsp;")
instance C_PCDATA Ent17 where
    pcdata s = PCDATA_17 [] (s2b_escape s)
    pcdata_bs = PCDATA_17 []
    ce_quot = PCDATA_17 [] (s2b "&quot;")
    ce_amp = PCDATA_17 [] (s2b "&amp;")
    ce_lt = PCDATA_17 [] (s2b "&lt;")
    ce_gt = PCDATA_17 [] (s2b "&gt;")
    ce_copy = PCDATA_17 [] (s2b "&copy;")
    ce_reg = PCDATA_17 [] (s2b "&reg;")
    ce_nbsp = PCDATA_17 [] (s2b "&nbsp;")
instance C_PCDATA Ent22 where
    pcdata s = PCDATA_22 [] (s2b_escape s)
    pcdata_bs = PCDATA_22 []
    ce_quot = PCDATA_22 [] (s2b "&quot;")
    ce_amp = PCDATA_22 [] (s2b "&amp;")
    ce_lt = PCDATA_22 [] (s2b "&lt;")
    ce_gt = PCDATA_22 [] (s2b "&gt;")
    ce_copy = PCDATA_22 [] (s2b "&copy;")
    ce_reg = PCDATA_22 [] (s2b "&reg;")
    ce_nbsp = PCDATA_22 [] (s2b "&nbsp;")
instance C_PCDATA Ent27 where
    pcdata s = PCDATA_27 [] (s2b_escape s)
    pcdata_bs = PCDATA_27 []
    ce_quot = PCDATA_27 [] (s2b "&quot;")
    ce_amp = PCDATA_27 [] (s2b "&amp;")
    ce_lt = PCDATA_27 [] (s2b "&lt;")
    ce_gt = PCDATA_27 [] (s2b "&gt;")
    ce_copy = PCDATA_27 [] (s2b "&copy;")
    ce_reg = PCDATA_27 [] (s2b "&reg;")
    ce_nbsp = PCDATA_27 [] (s2b "&nbsp;")
instance C_PCDATA Ent29 where
    pcdata s = PCDATA_29 [] (s2b_escape s)
    pcdata_bs = PCDATA_29 []
    ce_quot = PCDATA_29 [] (s2b "&quot;")
    ce_amp = PCDATA_29 [] (s2b "&amp;")
    ce_lt = PCDATA_29 [] (s2b "&lt;")
    ce_gt = PCDATA_29 [] (s2b "&gt;")
    ce_copy = PCDATA_29 [] (s2b "&copy;")
    ce_reg = PCDATA_29 [] (s2b "&reg;")
    ce_nbsp = PCDATA_29 [] (s2b "&nbsp;")
instance C_PCDATA Ent30 where
    pcdata s = PCDATA_30 [] (s2b_escape s)
    pcdata_bs = PCDATA_30 []
    ce_quot = PCDATA_30 [] (s2b "&quot;")
    ce_amp = PCDATA_30 [] (s2b "&amp;")
    ce_lt = PCDATA_30 [] (s2b "&lt;")
    ce_gt = PCDATA_30 [] (s2b "&gt;")
    ce_copy = PCDATA_30 [] (s2b "&copy;")
    ce_reg = PCDATA_30 [] (s2b "&reg;")
    ce_nbsp = PCDATA_30 [] (s2b "&nbsp;")
instance C_PCDATA Ent31 where
    pcdata s = PCDATA_31 [] (s2b_escape s)
    pcdata_bs = PCDATA_31 []
    ce_quot = PCDATA_31 [] (s2b "&quot;")
    ce_amp = PCDATA_31 [] (s2b "&amp;")
    ce_lt = PCDATA_31 [] (s2b "&lt;")
    ce_gt = PCDATA_31 [] (s2b "&gt;")
    ce_copy = PCDATA_31 [] (s2b "&copy;")
    ce_reg = PCDATA_31 [] (s2b "&reg;")
    ce_nbsp = PCDATA_31 [] (s2b "&nbsp;")
instance C_PCDATA Ent35 where
    pcdata s = PCDATA_35 [] (s2b_escape s)
    pcdata_bs = PCDATA_35 []
    ce_quot = PCDATA_35 [] (s2b "&quot;")
    ce_amp = PCDATA_35 [] (s2b "&amp;")
    ce_lt = PCDATA_35 [] (s2b "&lt;")
    ce_gt = PCDATA_35 [] (s2b "&gt;")
    ce_copy = PCDATA_35 [] (s2b "&copy;")
    ce_reg = PCDATA_35 [] (s2b "&reg;")
    ce_nbsp = PCDATA_35 [] (s2b "&nbsp;")
instance C_PCDATA Ent37 where
    pcdata s = PCDATA_37 [] (s2b_escape s)
    pcdata_bs = PCDATA_37 []
    ce_quot = PCDATA_37 [] (s2b "&quot;")
    ce_amp = PCDATA_37 [] (s2b "&amp;")
    ce_lt = PCDATA_37 [] (s2b "&lt;")
    ce_gt = PCDATA_37 [] (s2b "&gt;")
    ce_copy = PCDATA_37 [] (s2b "&copy;")
    ce_reg = PCDATA_37 [] (s2b "&reg;")
    ce_nbsp = PCDATA_37 [] (s2b "&nbsp;")
instance C_PCDATA Ent38 where
    pcdata s = PCDATA_38 [] (s2b_escape s)
    pcdata_bs = PCDATA_38 []
    ce_quot = PCDATA_38 [] (s2b "&quot;")
    ce_amp = PCDATA_38 [] (s2b "&amp;")
    ce_lt = PCDATA_38 [] (s2b "&lt;")
    ce_gt = PCDATA_38 [] (s2b "&gt;")
    ce_copy = PCDATA_38 [] (s2b "&copy;")
    ce_reg = PCDATA_38 [] (s2b "&reg;")
    ce_nbsp = PCDATA_38 [] (s2b "&nbsp;")
instance C_PCDATA Ent41 where
    pcdata s = PCDATA_41 [] (s2b_escape s)
    pcdata_bs = PCDATA_41 []
    ce_quot = PCDATA_41 [] (s2b "&quot;")
    ce_amp = PCDATA_41 [] (s2b "&amp;")
    ce_lt = PCDATA_41 [] (s2b "&lt;")
    ce_gt = PCDATA_41 [] (s2b "&gt;")
    ce_copy = PCDATA_41 [] (s2b "&copy;")
    ce_reg = PCDATA_41 [] (s2b "&reg;")
    ce_nbsp = PCDATA_41 [] (s2b "&nbsp;")
instance C_PCDATA Ent42 where
    pcdata s = PCDATA_42 [] (s2b_escape s)
    pcdata_bs = PCDATA_42 []
    ce_quot = PCDATA_42 [] (s2b "&quot;")
    ce_amp = PCDATA_42 [] (s2b "&amp;")
    ce_lt = PCDATA_42 [] (s2b "&lt;")
    ce_gt = PCDATA_42 [] (s2b "&gt;")
    ce_copy = PCDATA_42 [] (s2b "&copy;")
    ce_reg = PCDATA_42 [] (s2b "&reg;")
    ce_nbsp = PCDATA_42 [] (s2b "&nbsp;")
instance C_PCDATA Ent47 where
    pcdata s = PCDATA_47 [] (s2b_escape s)
    pcdata_bs = PCDATA_47 []
    ce_quot = PCDATA_47 [] (s2b "&quot;")
    ce_amp = PCDATA_47 [] (s2b "&amp;")
    ce_lt = PCDATA_47 [] (s2b "&lt;")
    ce_gt = PCDATA_47 [] (s2b "&gt;")
    ce_copy = PCDATA_47 [] (s2b "&copy;")
    ce_reg = PCDATA_47 [] (s2b "&reg;")
    ce_nbsp = PCDATA_47 [] (s2b "&nbsp;")
instance C_PCDATA Ent52 where
    pcdata s = PCDATA_52 [] (s2b_escape s)
    pcdata_bs = PCDATA_52 []
    ce_quot = PCDATA_52 [] (s2b "&quot;")
    ce_amp = PCDATA_52 [] (s2b "&amp;")
    ce_lt = PCDATA_52 [] (s2b "&lt;")
    ce_gt = PCDATA_52 [] (s2b "&gt;")
    ce_copy = PCDATA_52 [] (s2b "&copy;")
    ce_reg = PCDATA_52 [] (s2b "&reg;")
    ce_nbsp = PCDATA_52 [] (s2b "&nbsp;")
instance C_PCDATA Ent56 where
    pcdata s = PCDATA_56 [] (s2b_escape s)
    pcdata_bs = PCDATA_56 []
    ce_quot = PCDATA_56 [] (s2b "&quot;")
    ce_amp = PCDATA_56 [] (s2b "&amp;")
    ce_lt = PCDATA_56 [] (s2b "&lt;")
    ce_gt = PCDATA_56 [] (s2b "&gt;")
    ce_copy = PCDATA_56 [] (s2b "&copy;")
    ce_reg = PCDATA_56 [] (s2b "&reg;")
    ce_nbsp = PCDATA_56 [] (s2b "&nbsp;")
instance C_PCDATA Ent59 where
    pcdata s = PCDATA_59 [] (s2b_escape s)
    pcdata_bs = PCDATA_59 []
    ce_quot = PCDATA_59 [] (s2b "&quot;")
    ce_amp = PCDATA_59 [] (s2b "&amp;")
    ce_lt = PCDATA_59 [] (s2b "&lt;")
    ce_gt = PCDATA_59 [] (s2b "&gt;")
    ce_copy = PCDATA_59 [] (s2b "&copy;")
    ce_reg = PCDATA_59 [] (s2b "&reg;")
    ce_nbsp = PCDATA_59 [] (s2b "&nbsp;")
instance C_PCDATA Ent60 where
    pcdata s = PCDATA_60 [] (s2b_escape s)
    pcdata_bs = PCDATA_60 []
    ce_quot = PCDATA_60 [] (s2b "&quot;")
    ce_amp = PCDATA_60 [] (s2b "&amp;")
    ce_lt = PCDATA_60 [] (s2b "&lt;")
    ce_gt = PCDATA_60 [] (s2b "&gt;")
    ce_copy = PCDATA_60 [] (s2b "&copy;")
    ce_reg = PCDATA_60 [] (s2b "&reg;")
    ce_nbsp = PCDATA_60 [] (s2b "&nbsp;")
instance C_PCDATA Ent62 where
    pcdata s = PCDATA_62 [] (s2b_escape s)
    pcdata_bs = PCDATA_62 []
    ce_quot = PCDATA_62 [] (s2b "&quot;")
    ce_amp = PCDATA_62 [] (s2b "&amp;")
    ce_lt = PCDATA_62 [] (s2b "&lt;")
    ce_gt = PCDATA_62 [] (s2b "&gt;")
    ce_copy = PCDATA_62 [] (s2b "&copy;")
    ce_reg = PCDATA_62 [] (s2b "&reg;")
    ce_nbsp = PCDATA_62 [] (s2b "&nbsp;")
instance C_PCDATA Ent63 where
    pcdata s = PCDATA_63 [] (s2b_escape s)
    pcdata_bs = PCDATA_63 []
    ce_quot = PCDATA_63 [] (s2b "&quot;")
    ce_amp = PCDATA_63 [] (s2b "&amp;")
    ce_lt = PCDATA_63 [] (s2b "&lt;")
    ce_gt = PCDATA_63 [] (s2b "&gt;")
    ce_copy = PCDATA_63 [] (s2b "&copy;")
    ce_reg = PCDATA_63 [] (s2b "&reg;")
    ce_nbsp = PCDATA_63 [] (s2b "&nbsp;")
instance C_PCDATA Ent64 where
    pcdata s = PCDATA_64 [] (s2b_escape s)
    pcdata_bs = PCDATA_64 []
    ce_quot = PCDATA_64 [] (s2b "&quot;")
    ce_amp = PCDATA_64 [] (s2b "&amp;")
    ce_lt = PCDATA_64 [] (s2b "&lt;")
    ce_gt = PCDATA_64 [] (s2b "&gt;")
    ce_copy = PCDATA_64 [] (s2b "&copy;")
    ce_reg = PCDATA_64 [] (s2b "&reg;")
    ce_nbsp = PCDATA_64 [] (s2b "&nbsp;")
instance C_PCDATA Ent68 where
    pcdata s = PCDATA_68 [] (s2b_escape s)
    pcdata_bs = PCDATA_68 []
    ce_quot = PCDATA_68 [] (s2b "&quot;")
    ce_amp = PCDATA_68 [] (s2b "&amp;")
    ce_lt = PCDATA_68 [] (s2b "&lt;")
    ce_gt = PCDATA_68 [] (s2b "&gt;")
    ce_copy = PCDATA_68 [] (s2b "&copy;")
    ce_reg = PCDATA_68 [] (s2b "&reg;")
    ce_nbsp = PCDATA_68 [] (s2b "&nbsp;")
instance C_PCDATA Ent70 where
    pcdata s = PCDATA_70 [] (s2b_escape s)
    pcdata_bs = PCDATA_70 []
    ce_quot = PCDATA_70 [] (s2b "&quot;")
    ce_amp = PCDATA_70 [] (s2b "&amp;")
    ce_lt = PCDATA_70 [] (s2b "&lt;")
    ce_gt = PCDATA_70 [] (s2b "&gt;")
    ce_copy = PCDATA_70 [] (s2b "&copy;")
    ce_reg = PCDATA_70 [] (s2b "&reg;")
    ce_nbsp = PCDATA_70 [] (s2b "&nbsp;")
instance C_PCDATA Ent71 where
    pcdata s = PCDATA_71 [] (s2b_escape s)
    pcdata_bs = PCDATA_71 []
    ce_quot = PCDATA_71 [] (s2b "&quot;")
    ce_amp = PCDATA_71 [] (s2b "&amp;")
    ce_lt = PCDATA_71 [] (s2b "&lt;")
    ce_gt = PCDATA_71 [] (s2b "&gt;")
    ce_copy = PCDATA_71 [] (s2b "&copy;")
    ce_reg = PCDATA_71 [] (s2b "&reg;")
    ce_nbsp = PCDATA_71 [] (s2b "&nbsp;")
instance C_PCDATA Ent74 where
    pcdata s = PCDATA_74 [] (s2b_escape s)
    pcdata_bs = PCDATA_74 []
    ce_quot = PCDATA_74 [] (s2b "&quot;")
    ce_amp = PCDATA_74 [] (s2b "&amp;")
    ce_lt = PCDATA_74 [] (s2b "&lt;")
    ce_gt = PCDATA_74 [] (s2b "&gt;")
    ce_copy = PCDATA_74 [] (s2b "&copy;")
    ce_reg = PCDATA_74 [] (s2b "&reg;")
    ce_nbsp = PCDATA_74 [] (s2b "&nbsp;")
instance C_PCDATA Ent75 where
    pcdata s = PCDATA_75 [] (s2b_escape s)
    pcdata_bs = PCDATA_75 []
    ce_quot = PCDATA_75 [] (s2b "&quot;")
    ce_amp = PCDATA_75 [] (s2b "&amp;")
    ce_lt = PCDATA_75 [] (s2b "&lt;")
    ce_gt = PCDATA_75 [] (s2b "&gt;")
    ce_copy = PCDATA_75 [] (s2b "&copy;")
    ce_reg = PCDATA_75 [] (s2b "&reg;")
    ce_nbsp = PCDATA_75 [] (s2b "&nbsp;")
instance C_PCDATA Ent80 where
    pcdata s = PCDATA_80 [] (s2b_escape s)
    pcdata_bs = PCDATA_80 []
    ce_quot = PCDATA_80 [] (s2b "&quot;")
    ce_amp = PCDATA_80 [] (s2b "&amp;")
    ce_lt = PCDATA_80 [] (s2b "&lt;")
    ce_gt = PCDATA_80 [] (s2b "&gt;")
    ce_copy = PCDATA_80 [] (s2b "&copy;")
    ce_reg = PCDATA_80 [] (s2b "&reg;")
    ce_nbsp = PCDATA_80 [] (s2b "&nbsp;")
instance C_PCDATA Ent85 where
    pcdata s = PCDATA_85 [] (s2b_escape s)
    pcdata_bs = PCDATA_85 []
    ce_quot = PCDATA_85 [] (s2b "&quot;")
    ce_amp = PCDATA_85 [] (s2b "&amp;")
    ce_lt = PCDATA_85 [] (s2b "&lt;")
    ce_gt = PCDATA_85 [] (s2b "&gt;")
    ce_copy = PCDATA_85 [] (s2b "&copy;")
    ce_reg = PCDATA_85 [] (s2b "&reg;")
    ce_nbsp = PCDATA_85 [] (s2b "&nbsp;")
instance C_PCDATA Ent89 where
    pcdata s = PCDATA_89 [] (s2b_escape s)
    pcdata_bs = PCDATA_89 []
    ce_quot = PCDATA_89 [] (s2b "&quot;")
    ce_amp = PCDATA_89 [] (s2b "&amp;")
    ce_lt = PCDATA_89 [] (s2b "&lt;")
    ce_gt = PCDATA_89 [] (s2b "&gt;")
    ce_copy = PCDATA_89 [] (s2b "&copy;")
    ce_reg = PCDATA_89 [] (s2b "&reg;")
    ce_nbsp = PCDATA_89 [] (s2b "&nbsp;")
instance C_PCDATA Ent92 where
    pcdata s = PCDATA_92 [] (s2b_escape s)
    pcdata_bs = PCDATA_92 []
    ce_quot = PCDATA_92 [] (s2b "&quot;")
    ce_amp = PCDATA_92 [] (s2b "&amp;")
    ce_lt = PCDATA_92 [] (s2b "&lt;")
    ce_gt = PCDATA_92 [] (s2b "&gt;")
    ce_copy = PCDATA_92 [] (s2b "&copy;")
    ce_reg = PCDATA_92 [] (s2b "&reg;")
    ce_nbsp = PCDATA_92 [] (s2b "&nbsp;")
instance C_PCDATA Ent94 where
    pcdata s = PCDATA_94 [] (s2b_escape s)
    pcdata_bs = PCDATA_94 []
    ce_quot = PCDATA_94 [] (s2b "&quot;")
    ce_amp = PCDATA_94 [] (s2b "&amp;")
    ce_lt = PCDATA_94 [] (s2b "&lt;")
    ce_gt = PCDATA_94 [] (s2b "&gt;")
    ce_copy = PCDATA_94 [] (s2b "&copy;")
    ce_reg = PCDATA_94 [] (s2b "&reg;")
    ce_nbsp = PCDATA_94 [] (s2b "&nbsp;")
instance C_PCDATA Ent97 where
    pcdata s = PCDATA_97 [] (s2b_escape s)
    pcdata_bs = PCDATA_97 []
    ce_quot = PCDATA_97 [] (s2b "&quot;")
    ce_amp = PCDATA_97 [] (s2b "&amp;")
    ce_lt = PCDATA_97 [] (s2b "&lt;")
    ce_gt = PCDATA_97 [] (s2b "&gt;")
    ce_copy = PCDATA_97 [] (s2b "&copy;")
    ce_reg = PCDATA_97 [] (s2b "&reg;")
    ce_nbsp = PCDATA_97 [] (s2b "&nbsp;")
instance C_PCDATA Ent99 where
    pcdata s = PCDATA_99 [] (s2b_escape s)
    pcdata_bs = PCDATA_99 []
    ce_quot = PCDATA_99 [] (s2b "&quot;")
    ce_amp = PCDATA_99 [] (s2b "&amp;")
    ce_lt = PCDATA_99 [] (s2b "&lt;")
    ce_gt = PCDATA_99 [] (s2b "&gt;")
    ce_copy = PCDATA_99 [] (s2b "&copy;")
    ce_reg = PCDATA_99 [] (s2b "&reg;")
    ce_nbsp = PCDATA_99 [] (s2b "&nbsp;")
instance C_PCDATA Ent100 where
    pcdata s = PCDATA_100 [] (s2b_escape s)
    pcdata_bs = PCDATA_100 []
    ce_quot = PCDATA_100 [] (s2b "&quot;")
    ce_amp = PCDATA_100 [] (s2b "&amp;")
    ce_lt = PCDATA_100 [] (s2b "&lt;")
    ce_gt = PCDATA_100 [] (s2b "&gt;")
    ce_copy = PCDATA_100 [] (s2b "&copy;")
    ce_reg = PCDATA_100 [] (s2b "&reg;")
    ce_nbsp = PCDATA_100 [] (s2b "&nbsp;")
instance C_PCDATA Ent101 where
    pcdata s = PCDATA_101 [] (s2b_escape s)
    pcdata_bs = PCDATA_101 []
    ce_quot = PCDATA_101 [] (s2b "&quot;")
    ce_amp = PCDATA_101 [] (s2b "&amp;")
    ce_lt = PCDATA_101 [] (s2b "&lt;")
    ce_gt = PCDATA_101 [] (s2b "&gt;")
    ce_copy = PCDATA_101 [] (s2b "&copy;")
    ce_reg = PCDATA_101 [] (s2b "&reg;")
    ce_nbsp = PCDATA_101 [] (s2b "&nbsp;")
instance C_PCDATA Ent102 where
    pcdata s = PCDATA_102 [] (s2b_escape s)
    pcdata_bs = PCDATA_102 []
    ce_quot = PCDATA_102 [] (s2b "&quot;")
    ce_amp = PCDATA_102 [] (s2b "&amp;")
    ce_lt = PCDATA_102 [] (s2b "&lt;")
    ce_gt = PCDATA_102 [] (s2b "&gt;")
    ce_copy = PCDATA_102 [] (s2b "&copy;")
    ce_reg = PCDATA_102 [] (s2b "&reg;")
    ce_nbsp = PCDATA_102 [] (s2b "&nbsp;")
instance C_PCDATA Ent104 where
    pcdata s = PCDATA_104 [] (s2b_escape s)
    pcdata_bs = PCDATA_104 []
    ce_quot = PCDATA_104 [] (s2b "&quot;")
    ce_amp = PCDATA_104 [] (s2b "&amp;")
    ce_lt = PCDATA_104 [] (s2b "&lt;")
    ce_gt = PCDATA_104 [] (s2b "&gt;")
    ce_copy = PCDATA_104 [] (s2b "&copy;")
    ce_reg = PCDATA_104 [] (s2b "&reg;")
    ce_nbsp = PCDATA_104 [] (s2b "&nbsp;")
instance C_PCDATA Ent105 where
    pcdata s = PCDATA_105 [] (s2b_escape s)
    pcdata_bs = PCDATA_105 []
    ce_quot = PCDATA_105 [] (s2b "&quot;")
    ce_amp = PCDATA_105 [] (s2b "&amp;")
    ce_lt = PCDATA_105 [] (s2b "&lt;")
    ce_gt = PCDATA_105 [] (s2b "&gt;")
    ce_copy = PCDATA_105 [] (s2b "&copy;")
    ce_reg = PCDATA_105 [] (s2b "&reg;")
    ce_nbsp = PCDATA_105 [] (s2b "&nbsp;")
instance C_PCDATA Ent109 where
    pcdata s = PCDATA_109 [] (s2b_escape s)
    pcdata_bs = PCDATA_109 []
    ce_quot = PCDATA_109 [] (s2b "&quot;")
    ce_amp = PCDATA_109 [] (s2b "&amp;")
    ce_lt = PCDATA_109 [] (s2b "&lt;")
    ce_gt = PCDATA_109 [] (s2b "&gt;")
    ce_copy = PCDATA_109 [] (s2b "&copy;")
    ce_reg = PCDATA_109 [] (s2b "&reg;")
    ce_nbsp = PCDATA_109 [] (s2b "&nbsp;")
instance C_PCDATA Ent112 where
    pcdata s = PCDATA_112 [] (s2b_escape s)
    pcdata_bs = PCDATA_112 []
    ce_quot = PCDATA_112 [] (s2b "&quot;")
    ce_amp = PCDATA_112 [] (s2b "&amp;")
    ce_lt = PCDATA_112 [] (s2b "&lt;")
    ce_gt = PCDATA_112 [] (s2b "&gt;")
    ce_copy = PCDATA_112 [] (s2b "&copy;")
    ce_reg = PCDATA_112 [] (s2b "&reg;")
    ce_nbsp = PCDATA_112 [] (s2b "&nbsp;")
instance C_PCDATA Ent113 where
    pcdata s = PCDATA_113 [] (s2b_escape s)
    pcdata_bs = PCDATA_113 []
    ce_quot = PCDATA_113 [] (s2b "&quot;")
    ce_amp = PCDATA_113 [] (s2b "&amp;")
    ce_lt = PCDATA_113 [] (s2b "&lt;")
    ce_gt = PCDATA_113 [] (s2b "&gt;")
    ce_copy = PCDATA_113 [] (s2b "&copy;")
    ce_reg = PCDATA_113 [] (s2b "&reg;")
    ce_nbsp = PCDATA_113 [] (s2b "&nbsp;")
instance C_PCDATA Ent114 where
    pcdata s = PCDATA_114 [] (s2b_escape s)
    pcdata_bs = PCDATA_114 []
    ce_quot = PCDATA_114 [] (s2b "&quot;")
    ce_amp = PCDATA_114 [] (s2b "&amp;")
    ce_lt = PCDATA_114 [] (s2b "&lt;")
    ce_gt = PCDATA_114 [] (s2b "&gt;")
    ce_copy = PCDATA_114 [] (s2b "&copy;")
    ce_reg = PCDATA_114 [] (s2b "&reg;")
    ce_nbsp = PCDATA_114 [] (s2b "&nbsp;")
instance C_PCDATA Ent116 where
    pcdata s = PCDATA_116 [] (s2b_escape s)
    pcdata_bs = PCDATA_116 []
    ce_quot = PCDATA_116 [] (s2b "&quot;")
    ce_amp = PCDATA_116 [] (s2b "&amp;")
    ce_lt = PCDATA_116 [] (s2b "&lt;")
    ce_gt = PCDATA_116 [] (s2b "&gt;")
    ce_copy = PCDATA_116 [] (s2b "&copy;")
    ce_reg = PCDATA_116 [] (s2b "&reg;")
    ce_nbsp = PCDATA_116 [] (s2b "&nbsp;")
instance C_PCDATA Ent117 where
    pcdata s = PCDATA_117 [] (s2b_escape s)
    pcdata_bs = PCDATA_117 []
    ce_quot = PCDATA_117 [] (s2b "&quot;")
    ce_amp = PCDATA_117 [] (s2b "&amp;")
    ce_lt = PCDATA_117 [] (s2b "&lt;")
    ce_gt = PCDATA_117 [] (s2b "&gt;")
    ce_copy = PCDATA_117 [] (s2b "&copy;")
    ce_reg = PCDATA_117 [] (s2b "&reg;")
    ce_nbsp = PCDATA_117 [] (s2b "&nbsp;")
instance C_PCDATA Ent121 where
    pcdata s = PCDATA_121 [] (s2b_escape s)
    pcdata_bs = PCDATA_121 []
    ce_quot = PCDATA_121 [] (s2b "&quot;")
    ce_amp = PCDATA_121 [] (s2b "&amp;")
    ce_lt = PCDATA_121 [] (s2b "&lt;")
    ce_gt = PCDATA_121 [] (s2b "&gt;")
    ce_copy = PCDATA_121 [] (s2b "&copy;")
    ce_reg = PCDATA_121 [] (s2b "&reg;")
    ce_nbsp = PCDATA_121 [] (s2b "&nbsp;")
instance C_PCDATA Ent124 where
    pcdata s = PCDATA_124 [] (s2b_escape s)
    pcdata_bs = PCDATA_124 []
    ce_quot = PCDATA_124 [] (s2b "&quot;")
    ce_amp = PCDATA_124 [] (s2b "&amp;")
    ce_lt = PCDATA_124 [] (s2b "&lt;")
    ce_gt = PCDATA_124 [] (s2b "&gt;")
    ce_copy = PCDATA_124 [] (s2b "&copy;")
    ce_reg = PCDATA_124 [] (s2b "&reg;")
    ce_nbsp = PCDATA_124 [] (s2b "&nbsp;")
instance C_PCDATA Ent127 where
    pcdata s = PCDATA_127 [] (s2b_escape s)
    pcdata_bs = PCDATA_127 []
    ce_quot = PCDATA_127 [] (s2b "&quot;")
    ce_amp = PCDATA_127 [] (s2b "&amp;")
    ce_lt = PCDATA_127 [] (s2b "&lt;")
    ce_gt = PCDATA_127 [] (s2b "&gt;")
    ce_copy = PCDATA_127 [] (s2b "&copy;")
    ce_reg = PCDATA_127 [] (s2b "&reg;")
    ce_nbsp = PCDATA_127 [] (s2b "&nbsp;")
instance C_PCDATA Ent128 where
    pcdata s = PCDATA_128 [] (s2b_escape s)
    pcdata_bs = PCDATA_128 []
    ce_quot = PCDATA_128 [] (s2b "&quot;")
    ce_amp = PCDATA_128 [] (s2b "&amp;")
    ce_lt = PCDATA_128 [] (s2b "&lt;")
    ce_gt = PCDATA_128 [] (s2b "&gt;")
    ce_copy = PCDATA_128 [] (s2b "&copy;")
    ce_reg = PCDATA_128 [] (s2b "&reg;")
    ce_nbsp = PCDATA_128 [] (s2b "&nbsp;")
instance C_PCDATA Ent133 where
    pcdata s = PCDATA_133 [] (s2b_escape s)
    pcdata_bs = PCDATA_133 []
    ce_quot = PCDATA_133 [] (s2b "&quot;")
    ce_amp = PCDATA_133 [] (s2b "&amp;")
    ce_lt = PCDATA_133 [] (s2b "&lt;")
    ce_gt = PCDATA_133 [] (s2b "&gt;")
    ce_copy = PCDATA_133 [] (s2b "&copy;")
    ce_reg = PCDATA_133 [] (s2b "&reg;")
    ce_nbsp = PCDATA_133 [] (s2b "&nbsp;")


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 "<?xml version=\"1.0\" encoding=\"UTF-8\"?>\n<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\"\n    \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">\n", s2b "<html ", renderAtts att , gt_byte, maprender c ,s2b "</html>"]
instance Render Ent0 where
    render_bs (Head_0 att c) = B.concat [head_byte_b,renderAtts att,gt_byte, maprender c,head_byte_e]
    render_bs (Body_0 att c) = B.concat [body_byte_b,renderAtts att,gt_byte, maprender c,body_byte_e]
instance Render Ent1 where
    render_bs (Title_1 att c) = B.concat [title_byte_b,renderAtts att,gt_byte, maprender c,title_byte_e]
    render_bs (Base_1 att) = B.concat [base_byte_b,renderAtts (att++[href_att []]),gts_byte]
    render_bs (Meta_1 att) = B.concat [meta_byte_b,renderAtts (att++[content_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++[type_att []]),gt_byte, maprender c,style_byte_e]
    render_bs (Script_1 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Object_1 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
instance Render Ent2 where
    render_bs (PCDATA_2 _ str) = str
instance Render Ent3 where
    render_bs (Script_3 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_3 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_3 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_3 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_3 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_3 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_3 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_3 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_3 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_3 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_3 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_3 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_3 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_3 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_3 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_3 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_3 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_3 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_3 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_3 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_3 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_3 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_3 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_3 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_3 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_3 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_3 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_3 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_3 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_3 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_3 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_3 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_3 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_3 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_3 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_3 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_3 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_3 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_3 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_3 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_3 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_3 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_3 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_3 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_3 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_3 att c) = B.concat [form_byte_b,renderAtts (att++[action_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_3 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_3 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_3 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_3 _ str) = str
instance Render Ent4 where
    render_bs (Script_4 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_4 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_4 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_4 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_4 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_4 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_4 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_4 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_4 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_4 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_4 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_4 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_4 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_4 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_4 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_4 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_4 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_4 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_4 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_4 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_4 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_4 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_4 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_4 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_4 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_4 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_4 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_4 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_4 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_4 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_4 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_4 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_4 _ str) = str
instance Render Ent5 where
    render_bs (PCDATA_5 _ str) = str
instance Render Ent6 where
    render_bs (Script_6 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_6 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_6 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_6 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_6 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_6 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_6 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_6 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_6 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_6 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_6 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_6 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_6 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_6 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_6 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_6 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_6 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_6 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_6 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_6 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_6 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_6 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_6 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_6 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_6 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_6 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_6 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_6 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_6 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_6 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_6 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_6 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_6 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_6 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_6 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_6 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_6 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_6 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_6 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_6 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_6 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_6 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_6 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_6 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Label_6 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_6 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_6 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_6 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_6 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_6 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_6 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_6 _ str) = str
instance Render Ent7 where
    render_bs (Script_7 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_7 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_7 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_7 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_7 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_7 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_7 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_7 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_7 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_7 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_7 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_7 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_7 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_7 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_7 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_7 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_7 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_7 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_7 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Form_7 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_7 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_7 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent8 where
    render_bs (Li_8 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent9 where
    render_bs (Dt_9 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_9 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent10 where
    render_bs (Script_10 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_10 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_10 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_10 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_10 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_10 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_10 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_10 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_10 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_10 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_10 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_10 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_10 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_10 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_10 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_10 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_10 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_10 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_10 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_10 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_10 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_10 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_10 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_10 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Map_10 att c) = B.concat [map_byte_b,renderAtts (att++[id_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++[rows_att [],cols_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++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_11 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_11 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_11 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_11 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_11 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_11 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_11 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_11 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_11 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_11 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_11 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_11 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_11 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_11 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_11 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_11 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_11 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_11 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Fieldset_11 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_11 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent12 where
    render_bs (Script_12 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_12 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_12 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_12 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_12 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_12 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_12 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_12 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_12 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_12 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_12 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_12 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_12 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_12 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_12 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_12 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_12 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_12 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_12 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_12 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_12 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_12 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_12 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_12 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_12 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_12 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_12 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_12 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_12 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_12 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_12 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_12 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_12 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_12 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_12 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_12 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_12 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_12 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_12 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_12 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_12 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_12 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_12 att c) = B.concat [map_byte_b,renderAtts (att++[id_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_12 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_12 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_12 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_12 _ str) = str
instance Render Ent13 where
    render_bs (Script_13 att c) = B.concat [script_byte_b,renderAtts (att++[type_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++[dir_att Ltr]),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 (Sub_13 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_13 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_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 (Big_13 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_13 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_13 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_13 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_13 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_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++[rows_att [],cols_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 (Li_14 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent15 where
    render_bs (Dt_15 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_15 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent16 where
    render_bs (Script_16 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_16 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_16 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_16 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_16 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_16 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_16 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_16 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_16 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_16 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_16 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_16 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_16 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_16 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_16 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_16 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_16 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_16 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_16 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_16 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_16 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_16 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_16 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_16 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Map_16 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_16 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_16 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_16 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_16 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_16 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_16 _ str) = str
instance Render Ent17 where
    render_bs (Script_17 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_17 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_17 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_17 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_17 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_17 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_17 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_17 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_17 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_17 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_17 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_17 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_17 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_17 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_17 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_17 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_17 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_17 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_17 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_17 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_17 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_17 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_17 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_17 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_17 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_17 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_17 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_17 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_17 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_17 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_17 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_17 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_17 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_17 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_17 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_17 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_17 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_17 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_17 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_17 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_17 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_17 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_17 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_17 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_17 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_17 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_17 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_17 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_17 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_17 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_17 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_17 _ str) = str
instance Render Ent18 where
    render_bs (Caption_18 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_18 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_18 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_18 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_18 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_18 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_18 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent19 where
    render_bs (Tr_19 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent20 where
    render_bs (Col_20 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent21 where
    render_bs (Th_21 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_21 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent22 where
    render_bs (Script_22 att c) = B.concat [script_byte_b,renderAtts (att++[type_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 (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 (Ins_22 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_22 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_22 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_22 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_22 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_22 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_22 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_22 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_22 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_22 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_22 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_22 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_22 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_22 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_22 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_22 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_22 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_22 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_22 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_22 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_22 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_22 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_22 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_22 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_22 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_22 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_22 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Label_22 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_22 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_22 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_22 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_22 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_22 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_22 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_22 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_22 _ str) = str
instance Render Ent23 where
    render_bs (Caption_23 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_23 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_23 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_23 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_23 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_23 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_23 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent24 where
    render_bs (Tr_24 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent25 where
    render_bs (Col_25 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent26 where
    render_bs (Th_26 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_26 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent27 where
    render_bs (Script_27 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_27 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_27 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_27 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_27 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_27 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_27 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_27 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_27 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_27 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_27 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_27 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_27 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_27 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_27 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_27 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_27 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_27 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_27 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (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++[dir_att Ltr]),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 (Object_27 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_27 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_27 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_27 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_27 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Label_27 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_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++[rows_att [],cols_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 (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++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_28 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_28 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_28 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_28 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_28 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_28 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_28 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_28 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_28 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_28 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_28 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_28 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_28 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_28 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_28 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_28 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_28 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_28 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_28 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Form_28 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_28 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_28 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent29 where
    render_bs (Script_29 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_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++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_29 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_29 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_29 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_29 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_29 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_29 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_29 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_29 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_29 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_29 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_29 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_29 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_29 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_29 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_29 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_29 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_29 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_29 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_29 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_29 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_29 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_29 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_29 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_29 _ str) = str
instance Render Ent30 where
    render_bs (PCDATA_30 _ str) = str
instance Render Ent31 where
    render_bs (Script_31 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_31 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_31 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_31 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_31 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_31 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_31 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_31 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_31 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_31 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_31 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_31 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_31 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_31 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_31 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_31 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_31 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_31 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_31 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_31 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_31 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_31 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_31 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_31 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_31 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_31 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_31 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_31 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_31 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_31 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_31 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_31 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_31 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_31 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_31 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_31 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_31 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_31 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_31 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_31 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_31 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_31 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_31 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_31 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Input_31 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_31 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_31 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_31 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_31 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_31 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_31 _ str) = str
instance Render Ent32 where
    render_bs (Script_32 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_32 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_32 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_32 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_32 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_32 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_32 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_32 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_32 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_32 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_32 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_32 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_32 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_32 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_32 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_32 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_32 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_32 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_32 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Form_32 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_32 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_32 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent33 where
    render_bs (Li_33 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent34 where
    render_bs (Dt_34 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_34 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent35 where
    render_bs (Script_35 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_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++[dir_att Ltr]),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 (Map_35 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_35 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_35 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_35 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_35 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_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++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_36 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_36 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_36 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_36 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_36 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_36 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_36 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_36 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_36 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_36 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_36 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_36 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_36 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_36 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_36 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_36 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_36 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_36 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Fieldset_36 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    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++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_37 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_37 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_37 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_37 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_37 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_37 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_37 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_37 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_37 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_37 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_37 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_37 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_37 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_37 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_37 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_37 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_37 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_37 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (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++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_37 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_37 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_37 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_37 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_37 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_37 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_37 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_37 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_37 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_37 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_37 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_37 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_37 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_37 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_37 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_37 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_37 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_37 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_37 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_37 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_37 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_37 att c) = B.concat [map_byte_b,renderAtts (att++[id_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_37 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_37 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_37 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_37 _ str) = str
instance Render Ent38 where
    render_bs (Script_38 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_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 (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++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_38 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_38 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_38 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_38 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_38 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_38 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_38 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_38 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_38 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_38 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_38 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_38 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_38 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_38 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_38 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_38 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_38 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_38 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_38 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_38 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_38 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_38 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_38 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_38 _ str) = str
instance Render Ent39 where
    render_bs (Li_39 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent40 where
    render_bs (Dt_40 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_40 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent41 where
    render_bs (Script_41 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_41 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_41 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_41 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_41 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),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 (Map_41 att c) = B.concat [map_byte_b,renderAtts (att++[id_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++[rows_att [],cols_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++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_42 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_42 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_42 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_42 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_42 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_42 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_42 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_42 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_42 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_42 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_42 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_42 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_42 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_42 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_42 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_42 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_42 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_42 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (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++[dir_att Ltr]),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 (Sub_42 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_42 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_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 (Big_42 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_42 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_42 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_42 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_42 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_42 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_42 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_42 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_42 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_42 _ str) = str
instance Render Ent43 where
    render_bs (Caption_43 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_43 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_43 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_43 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_43 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_43 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_43 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent44 where
    render_bs (Tr_44 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent45 where
    render_bs (Col_45 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent46 where
    render_bs (Th_46 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_46 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent47 where
    render_bs (Script_47 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_47 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_47 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_47 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_47 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_47 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_47 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_47 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_47 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_47 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_47 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_47 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_47 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_47 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_47 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_47 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_47 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_47 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_47 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (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++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_47 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_47 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_47 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_47 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_47 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_47 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_47 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_47 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_47 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_47 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_47 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_47 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_47 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_47 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_47 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_47 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_47 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_47 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_47 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_47 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_47 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_47 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_47 att c) = B.concat [form_byte_b,renderAtts (att++[action_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++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_47 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_47 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_47 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_47 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_47 _ str) = str
instance Render Ent48 where
    render_bs (Caption_48 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_48 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_48 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_48 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_48 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_48 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_48 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent49 where
    render_bs (Tr_49 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent50 where
    render_bs (Col_50 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent51 where
    render_bs (Th_51 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_51 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent52 where
    render_bs (Script_52 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_52 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_52 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_52 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_52 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_52 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_52 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_52 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_52 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_52 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_52 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_52 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_52 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_52 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_52 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_52 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_52 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_52 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_52 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_52 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_52 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_52 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_52 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_52 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_52 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_52 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_52 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_52 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_52 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_52 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_52 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_52 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_52 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_52 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_52 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_52 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_52 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_52 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_52 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_52 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_52 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_52 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_52 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_52 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_52 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Input_52 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_52 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_52 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_52 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_52 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_52 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_52 _ str) = str
instance Render Ent53 where
    render_bs (Script_53 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_53 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_53 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_53 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_53 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_53 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_53 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_53 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_53 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_53 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_53 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_53 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_53 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_53 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_53 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_53 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_53 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_53 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_53 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_53 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Form_53 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_53 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_53 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent54 where
    render_bs (Optgroup_54 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_54 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent55 where
    render_bs (Option_55 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent56 where
    render_bs (Script_56 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_56 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_56 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_56 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_56 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_56 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_56 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_56 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_56 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_56 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_56 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_56 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_56 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_56 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_56 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_56 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_56 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_56 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_56 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_56 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_56 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_56 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_56 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_56 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_56 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_56 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_56 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_56 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_56 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_56 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_56 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_56 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_56 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_56 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_56 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_56 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_56 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_56 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_56 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_56 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_56 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_56 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_56 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_56 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_56 _ str) = str
instance Render Ent57 where
    render_bs (Optgroup_57 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_57 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent58 where
    render_bs (Option_58 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent59 where
    render_bs (Script_59 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_59 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_59 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_59 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_59 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_59 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_59 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_59 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_59 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_59 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_59 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_59 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_59 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_59 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_59 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_59 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_59 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_59 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_59 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_59 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_59 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_59 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_59 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_59 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_59 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_59 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_59 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_59 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_59 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_59 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_59 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_59 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_59 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_59 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_59 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_59 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_59 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_59 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_59 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_59 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_59 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_59 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_59 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_59 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_59 _ str) = str
instance Render Ent60 where
    render_bs (Script_60 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_60 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_60 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_60 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_60 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_60 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_60 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_60 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_60 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_60 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_60 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_60 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_60 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_60 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_60 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_60 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_60 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_60 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_60 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_60 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_60 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_60 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_60 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_60 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_60 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_60 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_60 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_60 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_60 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_60 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_60 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_60 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_60 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_60 _ str) = str
instance Render Ent61 where
    render_bs (Script_61 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_61 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_61 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_61 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_61 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_61 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_61 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_61 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_61 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_61 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_61 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_61 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_61 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_61 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_61 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_61 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_61 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_61 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_61 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_61 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Form_61 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_61 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_61 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent62 where
    render_bs (Script_62 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_62 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_62 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_62 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_62 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_62 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_62 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_62 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_62 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_62 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_62 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_62 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_62 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_62 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_62 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_62 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_62 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_62 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_62 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_62 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_62 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_62 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_62 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_62 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_62 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_62 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_62 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_62 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_62 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_62 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_62 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_62 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_62 _ str) = str
instance Render Ent63 where
    render_bs (PCDATA_63 _ str) = str
instance Render Ent64 where
    render_bs (Script_64 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_64 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_64 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_64 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_64 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_64 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_64 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_64 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_64 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_64 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_64 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_64 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_64 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_64 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_64 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_64 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_64 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_64 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_64 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_64 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_64 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_64 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_64 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_64 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_64 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_64 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_64 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_64 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_64 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_64 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_64 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_64 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_64 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_64 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_64 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_64 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_64 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_64 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_64 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_64 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_64 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_64 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_64 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_64 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_64 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Input_64 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_64 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_64 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_64 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_64 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_64 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_64 _ str) = str
instance Render Ent65 where
    render_bs (Script_65 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_65 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_65 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_65 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_65 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_65 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_65 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_65 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_65 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_65 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_65 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_65 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_65 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_65 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_65 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_65 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_65 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_65 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_65 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Form_65 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_65 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_65 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent66 where
    render_bs (Li_66 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent67 where
    render_bs (Dt_67 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_67 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent68 where
    render_bs (Script_68 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_68 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_68 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_68 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_68 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_68 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_68 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_68 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_68 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_68 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_68 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_68 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_68 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_68 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_68 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_68 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_68 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_68 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_68 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_68 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_68 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_68 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_68 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_68 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_68 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Map_68 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_68 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_68 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_68 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_68 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_68 _ str) = str
instance Render Ent69 where
    render_bs (Script_69 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_69 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_69 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_69 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_69 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_69 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_69 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_69 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_69 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_69 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_69 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_69 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_69 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_69 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_69 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_69 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_69 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_69 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_69 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Fieldset_69 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_69 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent70 where
    render_bs (Script_70 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_70 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_70 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_70 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_70 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_70 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_70 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_70 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_70 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_70 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_70 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_70 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_70 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_70 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_70 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_70 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_70 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_70 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_70 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_70 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_70 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_70 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_70 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_70 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_70 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_70 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_70 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_70 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_70 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_70 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_70 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_70 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_70 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_70 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_70 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_70 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_70 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_70 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_70 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_70 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_70 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_70 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_70 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_70 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_70 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_70 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_70 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_70 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_70 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_70 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_70 _ str) = str
instance Render Ent71 where
    render_bs (Script_71 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_71 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_71 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_71 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_71 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_71 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_71 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_71 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_71 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_71 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_71 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_71 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_71 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_71 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_71 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_71 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_71 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_71 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_71 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_71 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_71 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_71 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_71 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_71 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_71 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_71 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_71 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_71 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_71 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_71 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_71 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_71 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_71 _ str) = str
instance Render Ent72 where
    render_bs (Li_72 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent73 where
    render_bs (Dt_73 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_73 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent74 where
    render_bs (Script_74 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_74 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_74 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_74 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_74 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_74 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_74 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_74 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_74 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_74 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_74 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_74 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_74 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_74 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_74 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_74 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_74 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_74 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_74 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_74 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_74 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_74 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_74 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_74 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_74 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Map_74 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_74 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_74 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_74 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_74 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_74 _ str) = str
instance Render Ent75 where
    render_bs (Script_75 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_75 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_75 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_75 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_75 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_75 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_75 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_75 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_75 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_75 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_75 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_75 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_75 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_75 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_75 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_75 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_75 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_75 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_75 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_75 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_75 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_75 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_75 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_75 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_75 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_75 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_75 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_75 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_75 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_75 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_75 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_75 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_75 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_75 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_75 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_75 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_75 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_75 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_75 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_75 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_75 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_75 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_75 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_75 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_75 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_75 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_75 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_75 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_75 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_75 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_75 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_75 _ str) = str
instance Render Ent76 where
    render_bs (Caption_76 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_76 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_76 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_76 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_76 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_76 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_76 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent77 where
    render_bs (Tr_77 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent78 where
    render_bs (Col_78 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent79 where
    render_bs (Th_79 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_79 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent80 where
    render_bs (Script_80 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_80 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_80 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_80 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_80 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_80 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_80 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_80 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_80 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_80 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_80 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_80 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_80 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_80 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_80 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_80 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_80 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_80 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_80 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_80 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_80 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_80 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_80 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_80 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_80 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_80 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_80 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_80 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_80 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_80 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_80 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_80 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_80 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_80 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_80 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_80 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_80 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_80 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_80 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_80 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_80 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_80 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_80 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_80 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_80 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Input_80 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_80 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_80 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_80 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_80 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_80 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_80 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_80 _ str) = str
instance Render Ent81 where
    render_bs (Caption_81 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_81 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_81 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_81 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_81 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_81 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_81 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent82 where
    render_bs (Tr_82 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent83 where
    render_bs (Col_83 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent84 where
    render_bs (Th_84 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_84 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent85 where
    render_bs (Script_85 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_85 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_85 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_85 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_85 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_85 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_85 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_85 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_85 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_85 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_85 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_85 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_85 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_85 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_85 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_85 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_85 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_85 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_85 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_85 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_85 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_85 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_85 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_85 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_85 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_85 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_85 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_85 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_85 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_85 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_85 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_85 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_85 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_85 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_85 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_85 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_85 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_85 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_85 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_85 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_85 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_85 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_85 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_85 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_85 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_85 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Input_85 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_85 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_85 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_85 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_85 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_85 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_85 _ str) = str
instance Render Ent86 where
    render_bs (Script_86 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_86 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_86 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_86 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_86 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_86 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_86 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_86 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_86 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_86 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_86 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_86 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_86 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_86 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_86 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_86 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_86 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_86 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_86 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_86 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Form_86 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_86 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_86 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent87 where
    render_bs (Optgroup_87 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_87 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent88 where
    render_bs (Option_88 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent89 where
    render_bs (Script_89 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_89 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_89 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_89 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_89 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_89 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_89 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_89 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_89 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_89 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_89 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_89 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_89 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_89 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_89 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_89 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_89 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_89 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_89 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_89 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_89 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_89 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_89 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_89 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_89 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_89 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_89 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_89 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_89 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_89 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_89 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_89 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_89 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_89 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_89 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_89 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_89 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_89 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_89 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_89 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_89 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_89 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_89 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_89 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_89 _ str) = str
instance Render Ent90 where
    render_bs (Optgroup_90 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_90 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent91 where
    render_bs (Option_91 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent92 where
    render_bs (Script_92 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_92 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_92 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_92 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_92 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_92 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_92 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_92 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_92 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_92 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_92 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_92 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_92 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_92 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_92 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_92 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_92 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_92 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_92 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_92 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_92 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_92 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_92 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_92 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_92 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_92 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_92 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_92 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_92 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_92 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_92 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_92 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_92 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_92 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_92 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_92 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_92 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_92 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_92 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_92 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_92 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_92 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_92 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_92 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_92 _ str) = str
instance Render Ent93 where
    render_bs (Script_93 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_93 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_93 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_93 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_93 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_93 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_93 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_93 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_93 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_93 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_93 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_93 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_93 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_93 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_93 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_93 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_93 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_93 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_93 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Form_93 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Fieldset_93 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_93 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent94 where
    render_bs (Script_94 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_94 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_94 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_94 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_94 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_94 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_94 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_94 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_94 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_94 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_94 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_94 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_94 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_94 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_94 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_94 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_94 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_94 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_94 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_94 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_94 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_94 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_94 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_94 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_94 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_94 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_94 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_94 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_94 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_94 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_94 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_94 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_94 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_94 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_94 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_94 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_94 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_94 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_94 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_94 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_94 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_94 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_94 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_94 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_94 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Label_94 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_94 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_94 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_94 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_94 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_94 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_94 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_94 _ str) = str
instance Render Ent95 where
    render_bs (Li_95 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent96 where
    render_bs (Dt_96 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_96 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent97 where
    render_bs (Script_97 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_97 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_97 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_97 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_97 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_97 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_97 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_97 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_97 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_97 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_97 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_97 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_97 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_97 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_97 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_97 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_97 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_97 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_97 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_97 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_97 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_97 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_97 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_97 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_97 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Map_97 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_97 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_97 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_97 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_97 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_97 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_97 _ str) = str
instance Render Ent98 where
    render_bs (Script_98 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_98 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_98 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_98 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_98 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_98 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_98 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_98 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_98 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_98 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_98 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_98 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_98 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_98 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_98 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_98 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_98 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_98 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_98 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Fieldset_98 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_98 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent99 where
    render_bs (PCDATA_99 _ str) = str
instance Render Ent100 where
    render_bs (Script_100 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_100 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_100 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_100 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_100 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_100 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_100 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_100 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_100 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_100 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_100 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_100 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_100 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_100 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_100 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_100 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_100 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_100 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_100 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_100 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_100 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_100 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_100 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_100 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_100 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_100 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_100 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_100 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_100 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_100 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_100 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_100 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_100 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_100 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_100 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_100 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_100 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_100 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_100 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_100 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_100 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_100 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_100 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_100 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_100 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_100 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_100 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_100 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_100 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_100 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_100 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_100 _ str) = str
instance Render Ent101 where
    render_bs (PCDATA_101 _ str) = str
instance Render Ent102 where
    render_bs (Script_102 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_102 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_102 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_102 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_102 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_102 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_102 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_102 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_102 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_102 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_102 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_102 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_102 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_102 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_102 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_102 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_102 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_102 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_102 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_102 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_102 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_102 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_102 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_102 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_102 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_102 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_102 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_102 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_102 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_102 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_102 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_102 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_102 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_102 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_102 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_102 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_102 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_102 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_102 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_102 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_102 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_102 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_102 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_102 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_102 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_102 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_102 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_102 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_102 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_102 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_102 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_102 _ str) = str
instance Render Ent103 where
    render_bs (Script_103 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_103 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_103 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_103 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_103 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_103 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_103 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_103 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_103 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_103 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_103 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_103 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_103 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_103 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_103 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_103 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_103 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_103 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_103 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_103 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Fieldset_103 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_103 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent104 where
    render_bs (PCDATA_104 _ str) = str
instance Render Ent105 where
    render_bs (Script_105 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_105 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_105 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_105 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_105 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_105 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_105 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_105 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_105 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_105 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_105 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_105 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_105 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_105 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_105 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_105 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_105 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_105 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_105 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_105 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_105 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_105 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_105 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_105 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_105 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_105 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_105 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_105 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_105 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_105 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_105 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_105 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_105 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_105 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_105 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_105 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_105 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_105 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_105 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_105 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_105 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_105 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_105 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_105 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_105 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_105 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_105 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_105 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_105 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_105 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_105 _ str) = str
instance Render Ent106 where
    render_bs (Script_106 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_106 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_106 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_106 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_106 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_106 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_106 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_106 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_106 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_106 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_106 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_106 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_106 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_106 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_106 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_106 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_106 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_106 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_106 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_106 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Fieldset_106 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_106 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent107 where
    render_bs (Optgroup_107 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_107 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent108 where
    render_bs (Option_108 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent109 where
    render_bs (Script_109 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_109 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_109 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_109 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_109 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_109 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_109 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_109 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_109 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_109 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_109 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_109 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_109 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_109 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_109 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_109 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_109 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_109 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_109 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_109 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_109 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_109 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_109 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_109 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_109 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_109 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_109 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_109 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_109 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_109 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_109 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_109 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_109 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_109 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_109 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_109 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_109 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_109 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_109 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_109 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_109 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_109 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_109 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_109 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_109 _ str) = str
instance Render Ent110 where
    render_bs (Optgroup_110 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_110 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent111 where
    render_bs (Option_111 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent112 where
    render_bs (Script_112 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_112 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_112 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_112 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_112 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_112 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_112 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_112 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_112 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_112 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_112 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_112 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_112 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_112 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_112 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_112 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_112 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_112 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_112 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_112 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_112 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_112 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_112 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_112 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_112 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_112 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_112 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_112 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_112 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_112 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_112 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_112 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_112 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_112 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_112 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_112 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_112 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_112 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_112 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_112 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_112 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_112 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_112 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_112 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_112 _ str) = str
instance Render Ent113 where
    render_bs (Script_113 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_113 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_113 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_113 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_113 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_113 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_113 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_113 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_113 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_113 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_113 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_113 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_113 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_113 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_113 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_113 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_113 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_113 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_113 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_113 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_113 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_113 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_113 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_113 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_113 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_113 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_113 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_113 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_113 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_113 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_113 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_113 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_113 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_113 _ str) = str
instance Render Ent114 where
    render_bs (Script_114 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_114 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_114 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_114 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_114 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_114 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_114 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_114 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_114 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_114 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_114 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_114 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_114 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_114 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_114 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_114 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_114 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_114 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_114 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_114 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_114 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_114 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_114 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_114 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_114 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_114 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_114 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_114 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_114 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_114 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_114 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_114 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_114 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_114 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_114 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_114 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_114 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_114 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_114 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_114 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_114 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_114 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_114 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_114 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_114 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_114 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_114 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_114 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_114 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_114 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_114 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_114 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_114 _ str) = str
instance Render Ent115 where
    render_bs (Script_115 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_115 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_115 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_115 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_115 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_115 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_115 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_115 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_115 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_115 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_115 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_115 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_115 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_115 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_115 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_115 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_115 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_115 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_115 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_115 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Fieldset_115 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_115 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent116 where
    render_bs (PCDATA_116 _ str) = str
instance Render Ent117 where
    render_bs (Script_117 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_117 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_117 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_117 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_117 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_117 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_117 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_117 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_117 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_117 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_117 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_117 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_117 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_117 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_117 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_117 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_117 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_117 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_117 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_117 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_117 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_117 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_117 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_117 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_117 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_117 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_117 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_117 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_117 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_117 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_117 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_117 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_117 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_117 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_117 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_117 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_117 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_117 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_117 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_117 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_117 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_117 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Param_117 att) = B.concat [param_byte_b,renderAtts att,gts_byte]
    render_bs (Img_117 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_117 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Input_117 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_117 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_117 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_117 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Button_117 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_117 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_117 _ str) = str
instance Render Ent118 where
    render_bs (Script_118 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_118 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_118 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_118 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_118 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_118 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_118 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_118 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_118 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_118 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_118 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_118 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_118 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_118 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_118 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_118 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_118 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_118 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_118 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Area_118 att) = B.concat [area_byte_b,renderAtts (att++[alt_att []]),gts_byte]
    render_bs (Fieldset_118 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Table_118 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
instance Render Ent119 where
    render_bs (Optgroup_119 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_119 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent120 where
    render_bs (Option_120 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent121 where
    render_bs (Script_121 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_121 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_121 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_121 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_121 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_121 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_121 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_121 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_121 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_121 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_121 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_121 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_121 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_121 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_121 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_121 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_121 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_121 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_121 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_121 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_121 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_121 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_121 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_121 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_121 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_121 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_121 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_121 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_121 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_121 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_121 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_121 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_121 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_121 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_121 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_121 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_121 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_121 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_121 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_121 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_121 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_121 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_121 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_121 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_121 _ str) = str
instance Render Ent122 where
    render_bs (Optgroup_122 att c) = B.concat [optgroup_byte_b,renderAtts (att++[label_att []]),gt_byte, maprender c,optgroup_byte_e]
    render_bs (Option_122 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent123 where
    render_bs (Option_123 att c) = B.concat [option_byte_b,renderAtts att,gt_byte, maprender c,option_byte_e]
instance Render Ent124 where
    render_bs (Script_124 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_124 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_124 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_124 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_124 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_124 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_124 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_124 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_124 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_124 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_124 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_124 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_124 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_124 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_124 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_124 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_124 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_124 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_124 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (Span_124 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_124 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_124 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_124 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_124 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_124 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_124 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_124 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_124 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_124 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_124 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_124 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_124 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_124 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_124 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_124 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_124 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_124 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_124 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_124 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_124 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_124 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_124 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_124 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Table_124 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_124 _ str) = str
instance Render Ent125 where
    render_bs (Li_125 att c) = B.concat [li_byte_b,renderAtts att,gt_byte, maprender c,li_byte_e]
instance Render Ent126 where
    render_bs (Dt_126 att c) = B.concat [dt_byte_b,renderAtts att,gt_byte, maprender c,dt_byte_e]
    render_bs (Dd_126 att c) = B.concat [dd_byte_b,renderAtts att,gt_byte, maprender c,dd_byte_e]
instance Render Ent127 where
    render_bs (Script_127 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Ins_127 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_127 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_127 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_127 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_127 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_127 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_127 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_127 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_127 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_127 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_127 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_127 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_127 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_127 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_127 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_127 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_127 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_127 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_127 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_127 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_127 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_127 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_127 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_127 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Map_127 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_127 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_127 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_127 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_127 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Button_127 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (PCDATA_127 _ str) = str
instance Render Ent128 where
    render_bs (Script_128 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_128 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_128 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_128 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_128 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_128 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_128 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_128 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_128 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_128 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_128 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_128 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_128 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_128 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_128 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_128 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_128 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_128 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_128 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_128 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_128 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_128 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_128 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_128 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_128 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_128 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_128 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_128 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_128 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_128 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_128 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_128 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_128 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_128 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_128 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_128 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_128 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_128 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_128 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_128 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_128 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_128 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_128 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_128 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Label_128 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_128 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_128 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_128 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_128 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_128 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_128 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_128 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_128 _ str) = str
instance Render Ent129 where
    render_bs (Caption_129 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_129 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_129 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_129 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_129 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_129 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_129 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent130 where
    render_bs (Tr_130 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent131 where
    render_bs (Col_131 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent132 where
    render_bs (Th_132 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_132 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]
instance Render Ent133 where
    render_bs (Script_133 att c) = B.concat [script_byte_b,renderAtts (att++[type_att []]),gt_byte, maprender c,script_byte_e]
    render_bs (Noscript_133 att c) = B.concat [noscript_byte_b,renderAtts att,gt_byte, maprender c,noscript_byte_e]
    render_bs (Div_133 att c) = B.concat [div_byte_b,renderAtts att,gt_byte, maprender c,div_byte_e]
    render_bs (P_133 att c) = B.concat [p_byte_b,renderAtts att,gt_byte, maprender c,p_byte_e]
    render_bs (H1_133 att c) = B.concat [h1_byte_b,renderAtts att,gt_byte, maprender c,h1_byte_e]
    render_bs (H2_133 att c) = B.concat [h2_byte_b,renderAtts att,gt_byte, maprender c,h2_byte_e]
    render_bs (H3_133 att c) = B.concat [h3_byte_b,renderAtts att,gt_byte, maprender c,h3_byte_e]
    render_bs (H4_133 att c) = B.concat [h4_byte_b,renderAtts att,gt_byte, maprender c,h4_byte_e]
    render_bs (H5_133 att c) = B.concat [h5_byte_b,renderAtts att,gt_byte, maprender c,h5_byte_e]
    render_bs (H6_133 att c) = B.concat [h6_byte_b,renderAtts att,gt_byte, maprender c,h6_byte_e]
    render_bs (Ul_133 att c) = B.concat [ul_byte_b,renderAtts att,gt_byte, maprender c,ul_byte_e]
    render_bs (Ol_133 att c) = B.concat [ol_byte_b,renderAtts att,gt_byte, maprender c,ol_byte_e]
    render_bs (Dl_133 att c) = B.concat [dl_byte_b,renderAtts att,gt_byte, maprender c,dl_byte_e]
    render_bs (Address_133 att c) = B.concat [address_byte_b,renderAtts att,gt_byte, maprender c,address_byte_e]
    render_bs (Hr_133 att) = B.concat [hr_byte_b,renderAtts att,gts_byte]
    render_bs (Pre_133 att c) = B.concat [pre_byte_b,renderAtts att,gt_byte, maprender c,pre_byte_e]
    render_bs (Blockquote_133 att c) = B.concat [blockquote_byte_b,renderAtts att,gt_byte, maprender c,blockquote_byte_e]
    render_bs (Ins_133 att c) = B.concat [ins_byte_b,renderAtts att,gt_byte, maprender c,ins_byte_e]
    render_bs (Del_133 att c) = B.concat [del_byte_b,renderAtts att,gt_byte, maprender c,del_byte_e]
    render_bs (A_133 att c) = B.concat [a_byte_b,renderAtts att,gt_byte, maprender c,a_byte_e]
    render_bs (Span_133 att c) = B.concat [span_byte_b,renderAtts att,gt_byte, maprender c,span_byte_e]
    render_bs (Bdo_133 att c) = B.concat [bdo_byte_b,renderAtts (att++[dir_att Ltr]),gt_byte, maprender c,bdo_byte_e]
    render_bs (Br_133 att) = B.concat [br_byte_b,renderAtts att,gts_byte]
    render_bs (Em_133 att c) = B.concat [em_byte_b,renderAtts att,gt_byte, maprender c,em_byte_e]
    render_bs (Strong_133 att c) = B.concat [strong_byte_b,renderAtts att,gt_byte, maprender c,strong_byte_e]
    render_bs (Dfn_133 att c) = B.concat [dfn_byte_b,renderAtts att,gt_byte, maprender c,dfn_byte_e]
    render_bs (Code_133 att c) = B.concat [code_byte_b,renderAtts att,gt_byte, maprender c,code_byte_e]
    render_bs (Samp_133 att c) = B.concat [samp_byte_b,renderAtts att,gt_byte, maprender c,samp_byte_e]
    render_bs (Kbd_133 att c) = B.concat [kbd_byte_b,renderAtts att,gt_byte, maprender c,kbd_byte_e]
    render_bs (Var_133 att c) = B.concat [var_byte_b,renderAtts att,gt_byte, maprender c,var_byte_e]
    render_bs (Cite_133 att c) = B.concat [cite_byte_b,renderAtts att,gt_byte, maprender c,cite_byte_e]
    render_bs (Abbr_133 att c) = B.concat [abbr_byte_b,renderAtts att,gt_byte, maprender c,abbr_byte_e]
    render_bs (Acronym_133 att c) = B.concat [acronym_byte_b,renderAtts att,gt_byte, maprender c,acronym_byte_e]
    render_bs (Q_133 att c) = B.concat [q_byte_b,renderAtts att,gt_byte, maprender c,q_byte_e]
    render_bs (Sub_133 att c) = B.concat [sub_byte_b,renderAtts att,gt_byte, maprender c,sub_byte_e]
    render_bs (Sup_133 att c) = B.concat [sup_byte_b,renderAtts att,gt_byte, maprender c,sup_byte_e]
    render_bs (Tt_133 att c) = B.concat [tt_byte_b,renderAtts att,gt_byte, maprender c,tt_byte_e]
    render_bs (I_133 att c) = B.concat [i_byte_b,renderAtts att,gt_byte, maprender c,i_byte_e]
    render_bs (B_133 att c) = B.concat [b_byte_b,renderAtts att,gt_byte, maprender c,b_byte_e]
    render_bs (Big_133 att c) = B.concat [big_byte_b,renderAtts att,gt_byte, maprender c,big_byte_e]
    render_bs (Small_133 att c) = B.concat [small_byte_b,renderAtts att,gt_byte, maprender c,small_byte_e]
    render_bs (Object_133 att c) = B.concat [object_byte_b,renderAtts att,gt_byte, maprender c,object_byte_e]
    render_bs (Img_133 att) = B.concat [img_byte_b,renderAtts (att++[src_att [],alt_att []]),gts_byte]
    render_bs (Map_133 att c) = B.concat [map_byte_b,renderAtts (att++[id_att []]),gt_byte, maprender c,map_byte_e]
    render_bs (Form_133 att c) = B.concat [form_byte_b,renderAtts (att++[action_att []]),gt_byte, maprender c,form_byte_e]
    render_bs (Label_133 att c) = B.concat [label_byte_b,renderAtts att,gt_byte, maprender c,label_byte_e]
    render_bs (Input_133 att) = B.concat [input_byte_b,renderAtts att,gts_byte]
    render_bs (Select_133 att c) = B.concat [select_byte_b,renderAtts att,gt_byte, maprender c,select_byte_e]
    render_bs (Textarea_133 att c) = B.concat [textarea_byte_b,renderAtts (att++[rows_att [],cols_att []]),gt_byte, maprender c,textarea_byte_e]
    render_bs (Fieldset_133 att c) = B.concat [fieldset_byte_b,renderAtts att,gt_byte, maprender c,fieldset_byte_e]
    render_bs (Legend_133 att c) = B.concat [legend_byte_b,renderAtts att,gt_byte, maprender c,legend_byte_e]
    render_bs (Button_133 att c) = B.concat [button_byte_b,renderAtts att,gt_byte, maprender c,button_byte_e]
    render_bs (Table_133 att c) = B.concat [table_byte_b,renderAtts att,gt_byte, maprender c,table_byte_e]
    render_bs (PCDATA_133 _ str) = str
instance Render Ent134 where
    render_bs (Caption_134 att c) = B.concat [caption_byte_b,renderAtts att,gt_byte, maprender c,caption_byte_e]
    render_bs (Thead_134 att c) = B.concat [thead_byte_b,renderAtts att,gt_byte, maprender c,thead_byte_e]
    render_bs (Tfoot_134 att c) = B.concat [tfoot_byte_b,renderAtts att,gt_byte, maprender c,tfoot_byte_e]
    render_bs (Tbody_134 att c) = B.concat [tbody_byte_b,renderAtts att,gt_byte, maprender c,tbody_byte_e]
    render_bs (Colgroup_134 att c) = B.concat [colgroup_byte_b,renderAtts att,gt_byte, maprender c,colgroup_byte_e]
    render_bs (Col_134 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
    render_bs (Tr_134 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent135 where
    render_bs (Tr_135 att c) = B.concat [tr_byte_b,renderAtts att,gt_byte, maprender c,tr_byte_e]
instance Render Ent136 where
    render_bs (Col_136 att) = B.concat [col_byte_b,renderAtts att,gts_byte]
instance Render Ent137 where
    render_bs (Th_137 att c) = B.concat [th_byte_b,renderAtts att,gt_byte, maprender c,th_byte_e]
    render_bs (Td_137 att c) = B.concat [td_byte_b,renderAtts att,gt_byte, maprender c,td_byte_e]

none_byte_b = s2b "<none"
none_byte_e = s2b "</none>\n"
cdata_byte_b = s2b "<CDATA"
cdata_byte_e = s2b "</CDATA>\n"
pcdata_byte_b = s2b "<PCDATA"
pcdata_byte_e = s2b "</PCDATA>\n"
td_byte_b = s2b "<td"
td_byte_e = s2b "</td>\n"
th_byte_b = s2b "<th"
th_byte_e = s2b "</th>\n"
tr_byte_b = s2b "<tr"
tr_byte_e = s2b "</tr>\n"
col_byte_b = s2b "<col"
col_byte_e = s2b "</col>\n"
colgroup_byte_b = s2b "<colgroup"
colgroup_byte_e = s2b "</colgroup>\n"
tbody_byte_b = s2b "<tbody"
tbody_byte_e = s2b "</tbody>\n"
tfoot_byte_b = s2b "<tfoot"
tfoot_byte_e = s2b "</tfoot>\n"
thead_byte_b = s2b "<thead"
thead_byte_e = s2b "</thead>\n"
caption_byte_b = s2b "<caption"
caption_byte_e = s2b "</caption>\n"
table_byte_b = s2b "<table"
table_byte_e = s2b "</table>\n"
button_byte_b = s2b "<button"
button_byte_e = s2b "</button>\n"
legend_byte_b = s2b "<legend"
legend_byte_e = s2b "</legend>\n"
fieldset_byte_b = s2b "<fieldset"
fieldset_byte_e = s2b "</fieldset>\n"
textarea_byte_b = s2b "<textarea"
textarea_byte_e = s2b "</textarea>\n"
option_byte_b = s2b "<option"
option_byte_e = s2b "</option>\n"
optgroup_byte_b = s2b "<optgroup"
optgroup_byte_e = s2b "</optgroup>\n"
select_byte_b = s2b "<select"
select_byte_e = s2b "</select>\n"
input_byte_b = s2b "<input"
input_byte_e = s2b "</input>\n"
label_byte_b = s2b "<label"
label_byte_e = s2b "</label>\n"
form_byte_b = s2b "<form"
form_byte_e = s2b "</form>\n"
area_byte_b = s2b "<area"
area_byte_e = s2b "</area>\n"
map_byte_b = s2b "<map"
map_byte_e = s2b "</map>\n"
img_byte_b = s2b "<img"
img_byte_e = s2b "</img>\n"
param_byte_b = s2b "<param"
param_byte_e = s2b "</param>\n"
object_byte_b = s2b "<object"
object_byte_e = s2b "</object>\n"
small_byte_b = s2b "<small"
small_byte_e = s2b "</small>\n"
big_byte_b = s2b "<big"
big_byte_e = s2b "</big>\n"
b_byte_b = s2b "<b"
b_byte_e = s2b "</b>\n"
i_byte_b = s2b "<i"
i_byte_e = s2b "</i>\n"
tt_byte_b = s2b "<tt"
tt_byte_e = s2b "</tt>\n"
sup_byte_b = s2b "<sup"
sup_byte_e = s2b "</sup>\n"
sub_byte_b = s2b "<sub"
sub_byte_e = s2b "</sub>\n"
q_byte_b = s2b "<q"
q_byte_e = s2b "</q>\n"
acronym_byte_b = s2b "<acronym"
acronym_byte_e = s2b "</acronym>\n"
abbr_byte_b = s2b "<abbr"
abbr_byte_e = s2b "</abbr>\n"
cite_byte_b = s2b "<cite"
cite_byte_e = s2b "</cite>\n"
var_byte_b = s2b "<var"
var_byte_e = s2b "</var>\n"
kbd_byte_b = s2b "<kbd"
kbd_byte_e = s2b "</kbd>\n"
samp_byte_b = s2b "<samp"
samp_byte_e = s2b "</samp>\n"
code_byte_b = s2b "<code"
code_byte_e = s2b "</code>\n"
dfn_byte_b = s2b "<dfn"
dfn_byte_e = s2b "</dfn>\n"
strong_byte_b = s2b "<strong"
strong_byte_e = s2b "</strong>\n"
em_byte_b = s2b "<em"
em_byte_e = s2b "</em>\n"
br_byte_b = s2b "<br"
br_byte_e = s2b "</br>\n"
bdo_byte_b = s2b "<bdo"
bdo_byte_e = s2b "</bdo>\n"
span_byte_b = s2b "<span"
span_byte_e = s2b "</span>\n"
a_byte_b = s2b "<a"
a_byte_e = s2b "</a>\n"
del_byte_b = s2b "<del"
del_byte_e = s2b "</del>\n"
ins_byte_b = s2b "<ins"
ins_byte_e = s2b "</ins>\n"
blockquote_byte_b = s2b "<blockquote"
blockquote_byte_e = s2b "</blockquote>\n"
pre_byte_b = s2b "<pre"
pre_byte_e = s2b "</pre>\n"
hr_byte_b = s2b "<hr"
hr_byte_e = s2b "</hr>\n"
address_byte_b = s2b "<address"
address_byte_e = s2b "</address>\n"
dd_byte_b = s2b "<dd"
dd_byte_e = s2b "</dd>\n"
dt_byte_b = s2b "<dt"
dt_byte_e = s2b "</dt>\n"
dl_byte_b = s2b "<dl"
dl_byte_e = s2b "</dl>\n"
li_byte_b = s2b "<li"
li_byte_e = s2b "</li>\n"
ol_byte_b = s2b "<ol"
ol_byte_e = s2b "</ol>\n"
ul_byte_b = s2b "<ul"
ul_byte_e = s2b "</ul>\n"
h6_byte_b = s2b "<h6"
h6_byte_e = s2b "</h6>\n"
h5_byte_b = s2b "<h5"
h5_byte_e = s2b "</h5>\n"
h4_byte_b = s2b "<h4"
h4_byte_e = s2b "</h4>\n"
h3_byte_b = s2b "<h3"
h3_byte_e = s2b "</h3>\n"
h2_byte_b = s2b "<h2"
h2_byte_e = s2b "</h2>\n"
h1_byte_b = s2b "<h1"
h1_byte_e = s2b "</h1>\n"
p_byte_b = s2b "<p"
p_byte_e = s2b "</p>\n"
div_byte_b = s2b "<div"
div_byte_e = s2b "</div>\n"
body_byte_b = s2b "<body"
body_byte_e = s2b "</body>\n"
noscript_byte_b = s2b "<noscript"
noscript_byte_e = s2b "</noscript>\n"
script_byte_b = s2b "<script"
script_byte_e = s2b "</script>\n"
style_byte_b = s2b "<style"
style_byte_e = s2b "</style>\n"
link_byte_b = s2b "<link"
link_byte_e = s2b "</link>\n"
meta_byte_b = s2b "<meta"
meta_byte_e = s2b "</meta>\n"
base_byte_b = s2b "<base"
base_byte_e = s2b "</base>\n"
title_byte_b = s2b "<title"
title_byte_e = s2b "</title>\n"
head_byte_b = s2b "<head"
head_byte_e = s2b "</head>\n"
html_byte_b = s2b "<html"
html_byte_e = s2b "</html>\n"

http_equiv_byte = s2b "http-equiv"
content_byte = s2b "content"
nohref_byte = s2b "nohref"
onkeydown_byte = s2b "onkeydown"
onkeyup_byte = s2b "onkeyup"
onreset_byte = s2b "onreset"
onmouseup_byte = s2b "onmouseup"
scope_byte = s2b "scope"
onmouseover_byte = s2b "onmouseover"
align_byte = s2b "align"
lang_byte = s2b "lang"
valign_byte = s2b "valign"
name_byte = s2b "name"
charset_byte = s2b "charset"
scheme_byte = s2b "scheme"
accept_charset_byte = s2b "accept-charset"
onmousedown_byte = s2b "onmousedown"
rev_byte = s2b "rev"
span_byte = s2b "span"
title_byte = s2b "title"
onclick_byte = s2b "onclick"
width_byte = s2b "width"
enctype_byte = s2b "enctype"
ismap_byte = s2b "ismap"
usemap_byte = s2b "usemap"
coords_byte = s2b "coords"
frame_byte = s2b "frame"
size_byte = s2b "size"
onblur_byte = s2b "onblur"
datetime_byte = s2b "datetime"
dir_byte = s2b "dir"
summary_byte = s2b "summary"
method_byte = s2b "method"
standby_byte = s2b "standby"
tabindex_byte = s2b "tabindex"
onmousemove_byte = s2b "onmousemove"
style_byte = s2b "style"
height_byte = s2b "height"
codetype_byte = s2b "codetype"
char_byte = s2b "char"
multiple_byte = s2b "multiple"
codebase_byte = s2b "codebase"
xmlns_byte = s2b "xmlns"
profile_byte = s2b "profile"
rel_byte = s2b "rel"
onsubmit_byte = s2b "onsubmit"
ondblclick_byte = s2b "ondblclick"
axis_byte = s2b "axis"
cols_byte = s2b "cols"
abbr_byte = s2b "abbr"
onchange_byte = s2b "onchange"
readonly_byte = s2b "readonly"
href_byte = s2b "href"
media_byte = s2b "media"
id_byte = s2b "id"
src_byte = s2b "src"
value_byte = s2b "value"
for_byte = s2b "for"
data_byte = s2b "data"
hreflang_byte = s2b "hreflang"
checked_byte = s2b "checked"
declare_byte = s2b "declare"
onkeypress_byte = s2b "onkeypress"
label_byte = s2b "label"
class_byte = s2b "class"
type_byte = s2b "type"
shape_byte = s2b "shape"
accesskey_byte = s2b "accesskey"
headers_byte = s2b "headers"
disabled_byte = s2b "disabled"
rules_byte = s2b "rules"
rows_byte = s2b "rows"
onfocus_byte = s2b "onfocus"
colspan_byte = s2b "colspan"
rowspan_byte = s2b "rowspan"
defer_byte = s2b "defer"
cellspacing_byte = s2b "cellspacing"
charoff_byte = s2b "charoff"
cite_byte = s2b "cite"
maxlength_byte = s2b "maxlength"
onselect_byte = s2b "onselect"
archive_byte = s2b "archive"
alt_byte = s2b "alt"
accept_byte = s2b "accept"
classid_byte = s2b "classid"
longdesc_byte = s2b "longdesc"
onmouseout_byte = s2b "onmouseout"
border_byte = s2b "border"
onunload_byte = s2b "onunload"
onload_byte = s2b "onload"
action_byte = s2b "action"
cellpadding_byte = s2b "cellpadding"
valuetype_byte = s2b "valuetype"
selected_byte = s2b "selected"

class TagStr a where
    tagStr :: a -> String
instance TagStr Ent where
    tagStr (Html _ _) = "html"
instance TagStr Ent0 where
    tagStr (Head_0 _ _) = "head"
    tagStr (Body_0 _ _) = "body"
instance TagStr Ent1 where
    tagStr (Title_1 _ _) = "title"
    tagStr (Base_1 _) = "base"
    tagStr (Meta_1 _) = "meta"
    tagStr (Link_1 _) = "link"
    tagStr (Style_1 _ _) = "style"
    tagStr (Script_1 _ _) = "script"
    tagStr (Object_1 _ _) = "object"
instance TagStr Ent2 where
    tagStr (PCDATA_2 _ _) = "pcdata"
instance TagStr Ent3 where
    tagStr (Script_3 _ _) = "script"
    tagStr (Noscript_3 _ _) = "noscript"
    tagStr (Div_3 _ _) = "div"
    tagStr (P_3 _ _) = "p"
    tagStr (H1_3 _ _) = "h1"
    tagStr (H2_3 _ _) = "h2"
    tagStr (H3_3 _ _) = "h3"
    tagStr (H4_3 _ _) = "h4"
    tagStr (H5_3 _ _) = "h5"
    tagStr (H6_3 _ _) = "h6"
    tagStr (Ul_3 _ _) = "ul"
    tagStr (Ol_3 _ _) = "ol"
    tagStr (Dl_3 _ _) = "dl"
    tagStr (Address_3 _ _) = "address"
    tagStr (Hr_3 _) = "hr"
    tagStr (Pre_3 _ _) = "pre"
    tagStr (Blockquote_3 _ _) = "blockquote"
    tagStr (Ins_3 _ _) = "ins"
    tagStr (Del_3 _ _) = "del"
    tagStr (A_3 _ _) = "a"
    tagStr (Span_3 _ _) = "span"
    tagStr (Bdo_3 _ _) = "bdo"
    tagStr (Br_3 _) = "br"
    tagStr (Em_3 _ _) = "em"
    tagStr (Strong_3 _ _) = "strong"
    tagStr (Dfn_3 _ _) = "dfn"
    tagStr (Code_3 _ _) = "code"
    tagStr (Samp_3 _ _) = "samp"
    tagStr (Kbd_3 _ _) = "kbd"
    tagStr (Var_3 _ _) = "var"
    tagStr (Cite_3 _ _) = "cite"
    tagStr (Abbr_3 _ _) = "abbr"
    tagStr (Acronym_3 _ _) = "acronym"
    tagStr (Q_3 _ _) = "q"
    tagStr (Sub_3 _ _) = "sub"
    tagStr (Sup_3 _ _) = "sup"
    tagStr (Tt_3 _ _) = "tt"
    tagStr (I_3 _ _) = "i"
    tagStr (B_3 _ _) = "b"
    tagStr (Big_3 _ _) = "big"
    tagStr (Small_3 _ _) = "small"
    tagStr (Object_3 _ _) = "object"
    tagStr (Param_3 _) = "param"
    tagStr (Img_3 _) = "img"
    tagStr (Map_3 _ _) = "map"
    tagStr (Form_3 _ _) = "form"
    tagStr (Label_3 _ _) = "label"
    tagStr (Input_3 _) = "input"
    tagStr (Select_3 _ _) = "select"
    tagStr (Textarea_3 _ _) = "textarea"
    tagStr (Fieldset_3 _ _) = "fieldset"
    tagStr (Button_3 _ _) = "button"
    tagStr (Table_3 _ _) = "table"
    tagStr (PCDATA_3 _ _) = "pcdata"
instance TagStr Ent4 where
    tagStr (Script_4 _ _) = "script"
    tagStr (Ins_4 _ _) = "ins"
    tagStr (Del_4 _ _) = "del"
    tagStr (Span_4 _ _) = "span"
    tagStr (Bdo_4 _ _) = "bdo"
    tagStr (Br_4 _) = "br"
    tagStr (Em_4 _ _) = "em"
    tagStr (Strong_4 _ _) = "strong"
    tagStr (Dfn_4 _ _) = "dfn"
    tagStr (Code_4 _ _) = "code"
    tagStr (Samp_4 _ _) = "samp"
    tagStr (Kbd_4 _ _) = "kbd"
    tagStr (Var_4 _ _) = "var"
    tagStr (Cite_4 _ _) = "cite"
    tagStr (Abbr_4 _ _) = "abbr"
    tagStr (Acronym_4 _ _) = "acronym"
    tagStr (Q_4 _ _) = "q"
    tagStr (Sub_4 _ _) = "sub"
    tagStr (Sup_4 _ _) = "sup"
    tagStr (Tt_4 _ _) = "tt"
    tagStr (I_4 _ _) = "i"
    tagStr (B_4 _ _) = "b"
    tagStr (Big_4 _ _) = "big"
    tagStr (Small_4 _ _) = "small"
    tagStr (Object_4 _ _) = "object"
    tagStr (Img_4 _) = "img"
    tagStr (Map_4 _ _) = "map"
    tagStr (Label_4 _ _) = "label"
    tagStr (Input_4 _) = "input"
    tagStr (Select_4 _ _) = "select"
    tagStr (Textarea_4 _ _) = "textarea"
    tagStr (Button_4 _ _) = "button"
    tagStr (PCDATA_4 _ _) = "pcdata"
instance TagStr Ent5 where
    tagStr (PCDATA_5 _ _) = "pcdata"
instance TagStr Ent6 where
    tagStr (Script_6 _ _) = "script"
    tagStr (Noscript_6 _ _) = "noscript"
    tagStr (Div_6 _ _) = "div"
    tagStr (P_6 _ _) = "p"
    tagStr (H1_6 _ _) = "h1"
    tagStr (H2_6 _ _) = "h2"
    tagStr (H3_6 _ _) = "h3"
    tagStr (H4_6 _ _) = "h4"
    tagStr (H5_6 _ _) = "h5"
    tagStr (H6_6 _ _) = "h6"
    tagStr (Ul_6 _ _) = "ul"
    tagStr (Ol_6 _ _) = "ol"
    tagStr (Dl_6 _ _) = "dl"
    tagStr (Address_6 _ _) = "address"
    tagStr (Hr_6 _) = "hr"
    tagStr (Pre_6 _ _) = "pre"
    tagStr (Blockquote_6 _ _) = "blockquote"
    tagStr (Ins_6 _ _) = "ins"
    tagStr (Del_6 _ _) = "del"
    tagStr (Span_6 _ _) = "span"
    tagStr (Bdo_6 _ _) = "bdo"
    tagStr (Br_6 _) = "br"
    tagStr (Em_6 _ _) = "em"
    tagStr (Strong_6 _ _) = "strong"
    tagStr (Dfn_6 _ _) = "dfn"
    tagStr (Code_6 _ _) = "code"
    tagStr (Samp_6 _ _) = "samp"
    tagStr (Kbd_6 _ _) = "kbd"
    tagStr (Var_6 _ _) = "var"
    tagStr (Cite_6 _ _) = "cite"
    tagStr (Abbr_6 _ _) = "abbr"
    tagStr (Acronym_6 _ _) = "acronym"
    tagStr (Q_6 _ _) = "q"
    tagStr (Sub_6 _ _) = "sub"
    tagStr (Sup_6 _ _) = "sup"
    tagStr (Tt_6 _ _) = "tt"
    tagStr (I_6 _ _) = "i"
    tagStr (B_6 _ _) = "b"
    tagStr (Big_6 _ _) = "big"
    tagStr (Small_6 _ _) = "small"
    tagStr (Object_6 _ _) = "object"
    tagStr (Img_6 _) = "img"
    tagStr (Map_6 _ _) = "map"
    tagStr (Form_6 _ _) = "form"
    tagStr (Label_6 _ _) = "label"
    tagStr (Input_6 _) = "input"
    tagStr (Select_6 _ _) = "select"
    tagStr (Textarea_6 _ _) = "textarea"
    tagStr (Fieldset_6 _ _) = "fieldset"
    tagStr (Button_6 _ _) = "button"
    tagStr (Table_6 _ _) = "table"
    tagStr (PCDATA_6 _ _) = "pcdata"
instance TagStr Ent7 where
    tagStr (Script_7 _ _) = "script"
    tagStr (Noscript_7 _ _) = "noscript"
    tagStr (Div_7 _ _) = "div"
    tagStr (P_7 _ _) = "p"
    tagStr (H1_7 _ _) = "h1"
    tagStr (H2_7 _ _) = "h2"
    tagStr (H3_7 _ _) = "h3"
    tagStr (H4_7 _ _) = "h4"
    tagStr (H5_7 _ _) = "h5"
    tagStr (H6_7 _ _) = "h6"
    tagStr (Ul_7 _ _) = "ul"
    tagStr (Ol_7 _ _) = "ol"
    tagStr (Dl_7 _ _) = "dl"
    tagStr (Address_7 _ _) = "address"
    tagStr (Hr_7 _) = "hr"
    tagStr (Pre_7 _ _) = "pre"
    tagStr (Blockquote_7 _ _) = "blockquote"
    tagStr (Ins_7 _ _) = "ins"
    tagStr (Del_7 _ _) = "del"
    tagStr (Form_7 _ _) = "form"
    tagStr (Fieldset_7 _ _) = "fieldset"
    tagStr (Table_7 _ _) = "table"
instance TagStr Ent8 where
    tagStr (Li_8 _ _) = "li"
instance TagStr Ent9 where
    tagStr (Dt_9 _ _) = "dt"
    tagStr (Dd_9 _ _) = "dd"
instance TagStr Ent10 where
    tagStr (Script_10 _ _) = "script"
    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 (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 (Div_11 _ _) = "div"
    tagStr (P_11 _ _) = "p"
    tagStr (H1_11 _ _) = "h1"
    tagStr (H2_11 _ _) = "h2"
    tagStr (H3_11 _ _) = "h3"
    tagStr (H4_11 _ _) = "h4"
    tagStr (H5_11 _ _) = "h5"
    tagStr (H6_11 _ _) = "h6"
    tagStr (Ul_11 _ _) = "ul"
    tagStr (Ol_11 _ _) = "ol"
    tagStr (Dl_11 _ _) = "dl"
    tagStr (Address_11 _ _) = "address"
    tagStr (Hr_11 _) = "hr"
    tagStr (Pre_11 _ _) = "pre"
    tagStr (Blockquote_11 _ _) = "blockquote"
    tagStr (Ins_11 _ _) = "ins"
    tagStr (Del_11 _ _) = "del"
    tagStr (Fieldset_11 _ _) = "fieldset"
    tagStr (Table_11 _ _) = "table"
instance TagStr Ent12 where
    tagStr (Script_12 _ _) = "script"
    tagStr (Noscript_12 _ _) = "noscript"
    tagStr (Div_12 _ _) = "div"
    tagStr (P_12 _ _) = "p"
    tagStr (H1_12 _ _) = "h1"
    tagStr (H2_12 _ _) = "h2"
    tagStr (H3_12 _ _) = "h3"
    tagStr (H4_12 _ _) = "h4"
    tagStr (H5_12 _ _) = "h5"
    tagStr (H6_12 _ _) = "h6"
    tagStr (Ul_12 _ _) = "ul"
    tagStr (Ol_12 _ _) = "ol"
    tagStr (Dl_12 _ _) = "dl"
    tagStr (Address_12 _ _) = "address"
    tagStr (Hr_12 _) = "hr"
    tagStr (Pre_12 _ _) = "pre"
    tagStr (Blockquote_12 _ _) = "blockquote"
    tagStr (Ins_12 _ _) = "ins"
    tagStr (Del_12 _ _) = "del"
    tagStr (Span_12 _ _) = "span"
    tagStr (Bdo_12 _ _) = "bdo"
    tagStr (Br_12 _) = "br"
    tagStr (Em_12 _ _) = "em"
    tagStr (Strong_12 _ _) = "strong"
    tagStr (Dfn_12 _ _) = "dfn"
    tagStr (Code_12 _ _) = "code"
    tagStr (Samp_12 _ _) = "samp"
    tagStr (Kbd_12 _ _) = "kbd"
    tagStr (Var_12 _ _) = "var"
    tagStr (Cite_12 _ _) = "cite"
    tagStr (Abbr_12 _ _) = "abbr"
    tagStr (Acronym_12 _ _) = "acronym"
    tagStr (Q_12 _ _) = "q"
    tagStr (Sub_12 _ _) = "sub"
    tagStr (Sup_12 _ _) = "sup"
    tagStr (Tt_12 _ _) = "tt"
    tagStr (I_12 _ _) = "i"
    tagStr (B_12 _ _) = "b"
    tagStr (Big_12 _ _) = "big"
    tagStr (Small_12 _ _) = "small"
    tagStr (Object_12 _ _) = "object"
    tagStr (Img_12 _) = "img"
    tagStr (Map_12 _ _) = "map"
    tagStr (Label_12 _ _) = "label"
    tagStr (Input_12 _) = "input"
    tagStr (Select_12 _ _) = "select"
    tagStr (Textarea_12 _ _) = "textarea"
    tagStr (Fieldset_12 _ _) = "fieldset"
    tagStr (Button_12 _ _) = "button"
    tagStr (Table_12 _ _) = "table"
    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 (Sub_13 _ _) = "sub"
    tagStr (Sup_13 _ _) = "sup"
    tagStr (Tt_13 _ _) = "tt"
    tagStr (I_13 _ _) = "i"
    tagStr (B_13 _ _) = "b"
    tagStr (Big_13 _ _) = "big"
    tagStr (Small_13 _ _) = "small"
    tagStr (Object_13 _ _) = "object"
    tagStr (Img_13 _) = "img"
    tagStr (Map_13 _ _) = "map"
    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 (Li_14 _ _) = "li"
instance TagStr Ent15 where
    tagStr (Dt_15 _ _) = "dt"
    tagStr (Dd_15 _ _) = "dd"
instance TagStr Ent16 where
    tagStr (Script_16 _ _) = "script"
    tagStr (Ins_16 _ _) = "ins"
    tagStr (Del_16 _ _) = "del"
    tagStr (Span_16 _ _) = "span"
    tagStr (Bdo_16 _ _) = "bdo"
    tagStr (Br_16 _) = "br"
    tagStr (Em_16 _ _) = "em"
    tagStr (Strong_16 _ _) = "strong"
    tagStr (Dfn_16 _ _) = "dfn"
    tagStr (Code_16 _ _) = "code"
    tagStr (Samp_16 _ _) = "samp"
    tagStr (Kbd_16 _ _) = "kbd"
    tagStr (Var_16 _ _) = "var"
    tagStr (Cite_16 _ _) = "cite"
    tagStr (Abbr_16 _ _) = "abbr"
    tagStr (Acronym_16 _ _) = "acronym"
    tagStr (Q_16 _ _) = "q"
    tagStr (Sub_16 _ _) = "sub"
    tagStr (Sup_16 _ _) = "sup"
    tagStr (Tt_16 _ _) = "tt"
    tagStr (I_16 _ _) = "i"
    tagStr (B_16 _ _) = "b"
    tagStr (Big_16 _ _) = "big"
    tagStr (Small_16 _ _) = "small"
    tagStr (Map_16 _ _) = "map"
    tagStr (Label_16 _ _) = "label"
    tagStr (Input_16 _) = "input"
    tagStr (Select_16 _ _) = "select"
    tagStr (Textarea_16 _ _) = "textarea"
    tagStr (Button_16 _ _) = "button"
    tagStr (PCDATA_16 _ _) = "pcdata"
instance TagStr Ent17 where
    tagStr (Script_17 _ _) = "script"
    tagStr (Noscript_17 _ _) = "noscript"
    tagStr (Div_17 _ _) = "div"
    tagStr (P_17 _ _) = "p"
    tagStr (H1_17 _ _) = "h1"
    tagStr (H2_17 _ _) = "h2"
    tagStr (H3_17 _ _) = "h3"
    tagStr (H4_17 _ _) = "h4"
    tagStr (H5_17 _ _) = "h5"
    tagStr (H6_17 _ _) = "h6"
    tagStr (Ul_17 _ _) = "ul"
    tagStr (Ol_17 _ _) = "ol"
    tagStr (Dl_17 _ _) = "dl"
    tagStr (Address_17 _ _) = "address"
    tagStr (Hr_17 _) = "hr"
    tagStr (Pre_17 _ _) = "pre"
    tagStr (Blockquote_17 _ _) = "blockquote"
    tagStr (Ins_17 _ _) = "ins"
    tagStr (Del_17 _ _) = "del"
    tagStr (Span_17 _ _) = "span"
    tagStr (Bdo_17 _ _) = "bdo"
    tagStr (Br_17 _) = "br"
    tagStr (Em_17 _ _) = "em"
    tagStr (Strong_17 _ _) = "strong"
    tagStr (Dfn_17 _ _) = "dfn"
    tagStr (Code_17 _ _) = "code"
    tagStr (Samp_17 _ _) = "samp"
    tagStr (Kbd_17 _ _) = "kbd"
    tagStr (Var_17 _ _) = "var"
    tagStr (Cite_17 _ _) = "cite"
    tagStr (Abbr_17 _ _) = "abbr"
    tagStr (Acronym_17 _ _) = "acronym"
    tagStr (Q_17 _ _) = "q"
    tagStr (Sub_17 _ _) = "sub"
    tagStr (Sup_17 _ _) = "sup"
    tagStr (Tt_17 _ _) = "tt"
    tagStr (I_17 _ _) = "i"
    tagStr (B_17 _ _) = "b"
    tagStr (Big_17 _ _) = "big"
    tagStr (Small_17 _ _) = "small"
    tagStr (Object_17 _ _) = "object"
    tagStr (Img_17 _) = "img"
    tagStr (Map_17 _ _) = "map"
    tagStr (Label_17 _ _) = "label"
    tagStr (Input_17 _) = "input"
    tagStr (Select_17 _ _) = "select"
    tagStr (Textarea_17 _ _) = "textarea"
    tagStr (Fieldset_17 _ _) = "fieldset"
    tagStr (Legend_17 _ _) = "legend"
    tagStr (Button_17 _ _) = "button"
    tagStr (Table_17 _ _) = "table"
    tagStr (PCDATA_17 _ _) = "pcdata"
instance TagStr Ent18 where
    tagStr (Caption_18 _ _) = "caption"
    tagStr (Thead_18 _ _) = "thead"
    tagStr (Tfoot_18 _ _) = "tfoot"
    tagStr (Tbody_18 _ _) = "tbody"
    tagStr (Colgroup_18 _ _) = "colgroup"
    tagStr (Col_18 _) = "col"
    tagStr (Tr_18 _ _) = "tr"
instance TagStr Ent19 where
    tagStr (Tr_19 _ _) = "tr"
instance TagStr Ent20 where
    tagStr (Col_20 _) = "col"
instance TagStr Ent21 where
    tagStr (Th_21 _ _) = "th"
    tagStr (Td_21 _ _) = "td"
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 (Dl_22 _ _) = "dl"
    tagStr (Address_22 _ _) = "address"
    tagStr (Hr_22 _) = "hr"
    tagStr (Pre_22 _ _) = "pre"
    tagStr (Blockquote_22 _ _) = "blockquote"
    tagStr (Ins_22 _ _) = "ins"
    tagStr (Del_22 _ _) = "del"
    tagStr (Span_22 _ _) = "span"
    tagStr (Bdo_22 _ _) = "bdo"
    tagStr (Br_22 _) = "br"
    tagStr (Em_22 _ _) = "em"
    tagStr (Strong_22 _ _) = "strong"
    tagStr (Dfn_22 _ _) = "dfn"
    tagStr (Code_22 _ _) = "code"
    tagStr (Samp_22 _ _) = "samp"
    tagStr (Kbd_22 _ _) = "kbd"
    tagStr (Var_22 _ _) = "var"
    tagStr (Cite_22 _ _) = "cite"
    tagStr (Abbr_22 _ _) = "abbr"
    tagStr (Acronym_22 _ _) = "acronym"
    tagStr (Q_22 _ _) = "q"
    tagStr (Sub_22 _ _) = "sub"
    tagStr (Sup_22 _ _) = "sup"
    tagStr (Tt_22 _ _) = "tt"
    tagStr (I_22 _ _) = "i"
    tagStr (B_22 _ _) = "b"
    tagStr (Big_22 _ _) = "big"
    tagStr (Small_22 _ _) = "small"
    tagStr (Object_22 _ _) = "object"
    tagStr (Img_22 _) = "img"
    tagStr (Map_22 _ _) = "map"
    tagStr (Form_22 _ _) = "form"
    tagStr (Label_22 _ _) = "label"
    tagStr (Input_22 _) = "input"
    tagStr (Select_22 _ _) = "select"
    tagStr (Textarea_22 _ _) = "textarea"
    tagStr (Fieldset_22 _ _) = "fieldset"
    tagStr (Legend_22 _ _) = "legend"
    tagStr (Button_22 _ _) = "button"
    tagStr (Table_22 _ _) = "table"
    tagStr (PCDATA_22 _ _) = "pcdata"
instance TagStr Ent23 where
    tagStr (Caption_23 _ _) = "caption"
    tagStr (Thead_23 _ _) = "thead"
    tagStr (Tfoot_23 _ _) = "tfoot"
    tagStr (Tbody_23 _ _) = "tbody"
    tagStr (Colgroup_23 _ _) = "colgroup"
    tagStr (Col_23 _) = "col"
    tagStr (Tr_23 _ _) = "tr"
instance TagStr Ent24 where
    tagStr (Tr_24 _ _) = "tr"
instance TagStr Ent25 where
    tagStr (Col_25 _) = "col"
instance TagStr Ent26 where
    tagStr (Th_26 _ _) = "th"
    tagStr (Td_26 _ _) = "td"
instance TagStr Ent27 where
    tagStr (Script_27 _ _) = "script"
    tagStr (Noscript_27 _ _) = "noscript"
    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 (Dl_27 _ _) = "dl"
    tagStr (Address_27 _ _) = "address"
    tagStr (Hr_27 _) = "hr"
    tagStr (Pre_27 _ _) = "pre"
    tagStr (Blockquote_27 _ _) = "blockquote"
    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 (Object_27 _ _) = "object"
    tagStr (Param_27 _) = "param"
    tagStr (Img_27 _) = "img"
    tagStr (Map_27 _ _) = "map"
    tagStr (Form_27 _ _) = "form"
    tagStr (Label_27 _ _) = "label"
    tagStr (Input_27 _) = "input"
    tagStr (Select_27 _ _) = "select"
    tagStr (Textarea_27 _ _) = "textarea"
    tagStr (Fieldset_27 _ _) = "fieldset"
    tagStr (Button_27 _ _) = "button"
    tagStr (Table_27 _ _) = "table"
    tagStr (PCDATA_27 _ _) = "pcdata"
instance TagStr Ent28 where
    tagStr (Script_28 _ _) = "script"
    tagStr (Noscript_28 _ _) = "noscript"
    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 (Dl_28 _ _) = "dl"
    tagStr (Address_28 _ _) = "address"
    tagStr (Hr_28 _) = "hr"
    tagStr (Pre_28 _ _) = "pre"
    tagStr (Blockquote_28 _ _) = "blockquote"
    tagStr (Ins_28 _ _) = "ins"
    tagStr (Del_28 _ _) = "del"
    tagStr (Area_28 _) = "area"
    tagStr (Form_28 _ _) = "form"
    tagStr (Fieldset_28 _ _) = "fieldset"
    tagStr (Table_28 _ _) = "table"
instance TagStr Ent29 where
    tagStr (Script_29 _ _) = "script"
    tagStr (Ins_29 _ _) = "ins"
    tagStr (Del_29 _ _) = "del"
    tagStr (Span_29 _ _) = "span"
    tagStr (Bdo_29 _ _) = "bdo"
    tagStr (Br_29 _) = "br"
    tagStr (Em_29 _ _) = "em"
    tagStr (Strong_29 _ _) = "strong"
    tagStr (Dfn_29 _ _) = "dfn"
    tagStr (Code_29 _ _) = "code"
    tagStr (Samp_29 _ _) = "samp"
    tagStr (Kbd_29 _ _) = "kbd"
    tagStr (Var_29 _ _) = "var"
    tagStr (Cite_29 _ _) = "cite"
    tagStr (Abbr_29 _ _) = "abbr"
    tagStr (Acronym_29 _ _) = "acronym"
    tagStr (Q_29 _ _) = "q"
    tagStr (Sub_29 _ _) = "sub"
    tagStr (Sup_29 _ _) = "sup"
    tagStr (Tt_29 _ _) = "tt"
    tagStr (I_29 _ _) = "i"
    tagStr (B_29 _ _) = "b"
    tagStr (Big_29 _ _) = "big"
    tagStr (Small_29 _ _) = "small"
    tagStr (Object_29 _ _) = "object"
    tagStr (Img_29 _) = "img"
    tagStr (Map_29 _ _) = "map"
    tagStr (Input_29 _) = "input"
    tagStr (Select_29 _ _) = "select"
    tagStr (Textarea_29 _ _) = "textarea"
    tagStr (Button_29 _ _) = "button"
    tagStr (PCDATA_29 _ _) = "pcdata"
instance TagStr Ent30 where
    tagStr (PCDATA_30 _ _) = "pcdata"
instance TagStr Ent31 where
    tagStr (Script_31 _ _) = "script"
    tagStr (Noscript_31 _ _) = "noscript"
    tagStr (Div_31 _ _) = "div"
    tagStr (P_31 _ _) = "p"
    tagStr (H1_31 _ _) = "h1"
    tagStr (H2_31 _ _) = "h2"
    tagStr (H3_31 _ _) = "h3"
    tagStr (H4_31 _ _) = "h4"
    tagStr (H5_31 _ _) = "h5"
    tagStr (H6_31 _ _) = "h6"
    tagStr (Ul_31 _ _) = "ul"
    tagStr (Ol_31 _ _) = "ol"
    tagStr (Dl_31 _ _) = "dl"
    tagStr (Address_31 _ _) = "address"
    tagStr (Hr_31 _) = "hr"
    tagStr (Pre_31 _ _) = "pre"
    tagStr (Blockquote_31 _ _) = "blockquote"
    tagStr (Ins_31 _ _) = "ins"
    tagStr (Del_31 _ _) = "del"
    tagStr (Span_31 _ _) = "span"
    tagStr (Bdo_31 _ _) = "bdo"
    tagStr (Br_31 _) = "br"
    tagStr (Em_31 _ _) = "em"
    tagStr (Strong_31 _ _) = "strong"
    tagStr (Dfn_31 _ _) = "dfn"
    tagStr (Code_31 _ _) = "code"
    tagStr (Samp_31 _ _) = "samp"
    tagStr (Kbd_31 _ _) = "kbd"
    tagStr (Var_31 _ _) = "var"
    tagStr (Cite_31 _ _) = "cite"
    tagStr (Abbr_31 _ _) = "abbr"
    tagStr (Acronym_31 _ _) = "acronym"
    tagStr (Q_31 _ _) = "q"
    tagStr (Sub_31 _ _) = "sub"
    tagStr (Sup_31 _ _) = "sup"
    tagStr (Tt_31 _ _) = "tt"
    tagStr (I_31 _ _) = "i"
    tagStr (B_31 _ _) = "b"
    tagStr (Big_31 _ _) = "big"
    tagStr (Small_31 _ _) = "small"
    tagStr (Object_31 _ _) = "object"
    tagStr (Img_31 _) = "img"
    tagStr (Map_31 _ _) = "map"
    tagStr (Form_31 _ _) = "form"
    tagStr (Input_31 _) = "input"
    tagStr (Select_31 _ _) = "select"
    tagStr (Textarea_31 _ _) = "textarea"
    tagStr (Fieldset_31 _ _) = "fieldset"
    tagStr (Button_31 _ _) = "button"
    tagStr (Table_31 _ _) = "table"
    tagStr (PCDATA_31 _ _) = "pcdata"
instance TagStr Ent32 where
    tagStr (Script_32 _ _) = "script"
    tagStr (Noscript_32 _ _) = "noscript"
    tagStr (Div_32 _ _) = "div"
    tagStr (P_32 _ _) = "p"
    tagStr (H1_32 _ _) = "h1"
    tagStr (H2_32 _ _) = "h2"
    tagStr (H3_32 _ _) = "h3"
    tagStr (H4_32 _ _) = "h4"
    tagStr (H5_32 _ _) = "h5"
    tagStr (H6_32 _ _) = "h6"
    tagStr (Ul_32 _ _) = "ul"
    tagStr (Ol_32 _ _) = "ol"
    tagStr (Dl_32 _ _) = "dl"
    tagStr (Address_32 _ _) = "address"
    tagStr (Hr_32 _) = "hr"
    tagStr (Pre_32 _ _) = "pre"
    tagStr (Blockquote_32 _ _) = "blockquote"
    tagStr (Ins_32 _ _) = "ins"
    tagStr (Del_32 _ _) = "del"
    tagStr (Form_32 _ _) = "form"
    tagStr (Fieldset_32 _ _) = "fieldset"
    tagStr (Table_32 _ _) = "table"
instance TagStr Ent33 where
    tagStr (Li_33 _ _) = "li"
instance TagStr Ent34 where
    tagStr (Dt_34 _ _) = "dt"
    tagStr (Dd_34 _ _) = "dd"
instance TagStr Ent35 where
    tagStr (Script_35 _ _) = "script"
    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 (Map_35 _ _) = "map"
    tagStr (Input_35 _) = "input"
    tagStr (Select_35 _ _) = "select"
    tagStr (Textarea_35 _ _) = "textarea"
    tagStr (Button_35 _ _) = "button"
    tagStr (PCDATA_35 _ _) = "pcdata"
instance TagStr Ent36 where
    tagStr (Script_36 _ _) = "script"
    tagStr (Noscript_36 _ _) = "noscript"
    tagStr (Div_36 _ _) = "div"
    tagStr (P_36 _ _) = "p"
    tagStr (H1_36 _ _) = "h1"
    tagStr (H2_36 _ _) = "h2"
    tagStr (H3_36 _ _) = "h3"
    tagStr (H4_36 _ _) = "h4"
    tagStr (H5_36 _ _) = "h5"
    tagStr (H6_36 _ _) = "h6"
    tagStr (Ul_36 _ _) = "ul"
    tagStr (Ol_36 _ _) = "ol"
    tagStr (Dl_36 _ _) = "dl"
    tagStr (Address_36 _ _) = "address"
    tagStr (Hr_36 _) = "hr"
    tagStr (Pre_36 _ _) = "pre"
    tagStr (Blockquote_36 _ _) = "blockquote"
    tagStr (Ins_36 _ _) = "ins"
    tagStr (Del_36 _ _) = "del"
    tagStr (Fieldset_36 _ _) = "fieldset"
    tagStr (Table_36 _ _) = "table"
instance TagStr Ent37 where
    tagStr (Script_37 _ _) = "script"
    tagStr (Noscript_37 _ _) = "noscript"
    tagStr (Div_37 _ _) = "div"
    tagStr (P_37 _ _) = "p"
    tagStr (H1_37 _ _) = "h1"
    tagStr (H2_37 _ _) = "h2"
    tagStr (H3_37 _ _) = "h3"
    tagStr (H4_37 _ _) = "h4"
    tagStr (H5_37 _ _) = "h5"
    tagStr (H6_37 _ _) = "h6"
    tagStr (Ul_37 _ _) = "ul"
    tagStr (Ol_37 _ _) = "ol"
    tagStr (Dl_37 _ _) = "dl"
    tagStr (Address_37 _ _) = "address"
    tagStr (Hr_37 _) = "hr"
    tagStr (Pre_37 _ _) = "pre"
    tagStr (Blockquote_37 _ _) = "blockquote"
    tagStr (Ins_37 _ _) = "ins"
    tagStr (Del_37 _ _) = "del"
    tagStr (Span_37 _ _) = "span"
    tagStr (Bdo_37 _ _) = "bdo"
    tagStr (Br_37 _) = "br"
    tagStr (Em_37 _ _) = "em"
    tagStr (Strong_37 _ _) = "strong"
    tagStr (Dfn_37 _ _) = "dfn"
    tagStr (Code_37 _ _) = "code"
    tagStr (Samp_37 _ _) = "samp"
    tagStr (Kbd_37 _ _) = "kbd"
    tagStr (Var_37 _ _) = "var"
    tagStr (Cite_37 _ _) = "cite"
    tagStr (Abbr_37 _ _) = "abbr"
    tagStr (Acronym_37 _ _) = "acronym"
    tagStr (Q_37 _ _) = "q"
    tagStr (Sub_37 _ _) = "sub"
    tagStr (Sup_37 _ _) = "sup"
    tagStr (Tt_37 _ _) = "tt"
    tagStr (I_37 _ _) = "i"
    tagStr (B_37 _ _) = "b"
    tagStr (Big_37 _ _) = "big"
    tagStr (Small_37 _ _) = "small"
    tagStr (Object_37 _ _) = "object"
    tagStr (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 (Table_37 _ _) = "table"
    tagStr (PCDATA_37 _ _) = "pcdata"
instance TagStr Ent38 where
    tagStr (Script_38 _ _) = "script"
    tagStr (Ins_38 _ _) = "ins"
    tagStr (Del_38 _ _) = "del"
    tagStr (Span_38 _ _) = "span"
    tagStr (Bdo_38 _ _) = "bdo"
    tagStr (Br_38 _) = "br"
    tagStr (Em_38 _ _) = "em"
    tagStr (Strong_38 _ _) = "strong"
    tagStr (Dfn_38 _ _) = "dfn"
    tagStr (Code_38 _ _) = "code"
    tagStr (Samp_38 _ _) = "samp"
    tagStr (Kbd_38 _ _) = "kbd"
    tagStr (Var_38 _ _) = "var"
    tagStr (Cite_38 _ _) = "cite"
    tagStr (Abbr_38 _ _) = "abbr"
    tagStr (Acronym_38 _ _) = "acronym"
    tagStr (Q_38 _ _) = "q"
    tagStr (Sub_38 _ _) = "sub"
    tagStr (Sup_38 _ _) = "sup"
    tagStr (Tt_38 _ _) = "tt"
    tagStr (I_38 _ _) = "i"
    tagStr (B_38 _ _) = "b"
    tagStr (Big_38 _ _) = "big"
    tagStr (Small_38 _ _) = "small"
    tagStr (Object_38 _ _) = "object"
    tagStr (Img_38 _) = "img"
    tagStr (Map_38 _ _) = "map"
    tagStr (Input_38 _) = "input"
    tagStr (Select_38 _ _) = "select"
    tagStr (Textarea_38 _ _) = "textarea"
    tagStr (Button_38 _ _) = "button"
    tagStr (PCDATA_38 _ _) = "pcdata"
instance TagStr Ent39 where
    tagStr (Li_39 _ _) = "li"
instance TagStr Ent40 where
    tagStr (Dt_40 _ _) = "dt"
    tagStr (Dd_40 _ _) = "dd"
instance TagStr Ent41 where
    tagStr (Script_41 _ _) = "script"
    tagStr (Ins_41 _ _) = "ins"
    tagStr (Del_41 _ _) = "del"
    tagStr (Span_41 _ _) = "span"
    tagStr (Bdo_41 _ _) = "bdo"
    tagStr (Br_41 _) = "br"
    tagStr (Em_41 _ _) = "em"
    tagStr (Strong_41 _ _) = "strong"
    tagStr (Dfn_41 _ _) = "dfn"
    tagStr (Code_41 _ _) = "code"
    tagStr (Samp_41 _ _) = "samp"
    tagStr (Kbd_41 _ _) = "kbd"
    tagStr (Var_41 _ _) = "var"
    tagStr (Cite_41 _ _) = "cite"
    tagStr (Abbr_41 _ _) = "abbr"
    tagStr (Acronym_41 _ _) = "acronym"
    tagStr (Q_41 _ _) = "q"
    tagStr (Sub_41 _ _) = "sub"
    tagStr (Sup_41 _ _) = "sup"
    tagStr (Tt_41 _ _) = "tt"
    tagStr (I_41 _ _) = "i"
    tagStr (B_41 _ _) = "b"
    tagStr (Big_41 _ _) = "big"
    tagStr (Small_41 _ _) = "small"
    tagStr (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 (Noscript_42 _ _) = "noscript"
    tagStr (Div_42 _ _) = "div"
    tagStr (P_42 _ _) = "p"
    tagStr (H1_42 _ _) = "h1"
    tagStr (H2_42 _ _) = "h2"
    tagStr (H3_42 _ _) = "h3"
    tagStr (H4_42 _ _) = "h4"
    tagStr (H5_42 _ _) = "h5"
    tagStr (H6_42 _ _) = "h6"
    tagStr (Ul_42 _ _) = "ul"
    tagStr (Ol_42 _ _) = "ol"
    tagStr (Dl_42 _ _) = "dl"
    tagStr (Address_42 _ _) = "address"
    tagStr (Hr_42 _) = "hr"
    tagStr (Pre_42 _ _) = "pre"
    tagStr (Blockquote_42 _ _) = "blockquote"
    tagStr (Ins_42 _ _) = "ins"
    tagStr (Del_42 _ _) = "del"
    tagStr (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 (Sub_42 _ _) = "sub"
    tagStr (Sup_42 _ _) = "sup"
    tagStr (Tt_42 _ _) = "tt"
    tagStr (I_42 _ _) = "i"
    tagStr (B_42 _ _) = "b"
    tagStr (Big_42 _ _) = "big"
    tagStr (Small_42 _ _) = "small"
    tagStr (Object_42 _ _) = "object"
    tagStr (Img_42 _) = "img"
    tagStr (Map_42 _ _) = "map"
    tagStr (Input_42 _) = "input"
    tagStr (Select_42 _ _) = "select"
    tagStr (Textarea_42 _ _) = "textarea"
    tagStr (Fieldset_42 _ _) = "fieldset"
    tagStr (Legend_42 _ _) = "legend"
    tagStr (Button_42 _ _) = "button"
    tagStr (Table_42 _ _) = "table"
    tagStr (PCDATA_42 _ _) = "pcdata"
instance TagStr Ent43 where
    tagStr (Caption_43 _ _) = "caption"
    tagStr (Thead_43 _ _) = "thead"
    tagStr (Tfoot_43 _ _) = "tfoot"
    tagStr (Tbody_43 _ _) = "tbody"
    tagStr (Colgroup_43 _ _) = "colgroup"
    tagStr (Col_43 _) = "col"
    tagStr (Tr_43 _ _) = "tr"
instance TagStr Ent44 where
    tagStr (Tr_44 _ _) = "tr"
instance TagStr Ent45 where
    tagStr (Col_45 _) = "col"
instance TagStr Ent46 where
    tagStr (Th_46 _ _) = "th"
    tagStr (Td_46 _ _) = "td"
instance TagStr Ent47 where
    tagStr (Script_47 _ _) = "script"
    tagStr (Noscript_47 _ _) = "noscript"
    tagStr (Div_47 _ _) = "div"
    tagStr (P_47 _ _) = "p"
    tagStr (H1_47 _ _) = "h1"
    tagStr (H2_47 _ _) = "h2"
    tagStr (H3_47 _ _) = "h3"
    tagStr (H4_47 _ _) = "h4"
    tagStr (H5_47 _ _) = "h5"
    tagStr (H6_47 _ _) = "h6"
    tagStr (Ul_47 _ _) = "ul"
    tagStr (Ol_47 _ _) = "ol"
    tagStr (Dl_47 _ _) = "dl"
    tagStr (Address_47 _ _) = "address"
    tagStr (Hr_47 _) = "hr"
    tagStr (Pre_47 _ _) = "pre"
    tagStr (Blockquote_47 _ _) = "blockquote"
    tagStr (Ins_47 _ _) = "ins"
    tagStr (Del_47 _ _) = "del"
    tagStr (Span_47 _ _) = "span"
    tagStr (Bdo_47 _ _) = "bdo"
    tagStr (Br_47 _) = "br"
    tagStr (Em_47 _ _) = "em"
    tagStr (Strong_47 _ _) = "strong"
    tagStr (Dfn_47 _ _) = "dfn"
    tagStr (Code_47 _ _) = "code"
    tagStr (Samp_47 _ _) = "samp"
    tagStr (Kbd_47 _ _) = "kbd"
    tagStr (Var_47 _ _) = "var"
    tagStr (Cite_47 _ _) = "cite"
    tagStr (Abbr_47 _ _) = "abbr"
    tagStr (Acronym_47 _ _) = "acronym"
    tagStr (Q_47 _ _) = "q"
    tagStr (Sub_47 _ _) = "sub"
    tagStr (Sup_47 _ _) = "sup"
    tagStr (Tt_47 _ _) = "tt"
    tagStr (I_47 _ _) = "i"
    tagStr (B_47 _ _) = "b"
    tagStr (Big_47 _ _) = "big"
    tagStr (Small_47 _ _) = "small"
    tagStr (Object_47 _ _) = "object"
    tagStr (Img_47 _) = "img"
    tagStr (Map_47 _ _) = "map"
    tagStr (Form_47 _ _) = "form"
    tagStr (Input_47 _) = "input"
    tagStr (Select_47 _ _) = "select"
    tagStr (Textarea_47 _ _) = "textarea"
    tagStr (Fieldset_47 _ _) = "fieldset"
    tagStr (Legend_47 _ _) = "legend"
    tagStr (Button_47 _ _) = "button"
    tagStr (Table_47 _ _) = "table"
    tagStr (PCDATA_47 _ _) = "pcdata"
instance TagStr Ent48 where
    tagStr (Caption_48 _ _) = "caption"
    tagStr (Thead_48 _ _) = "thead"
    tagStr (Tfoot_48 _ _) = "tfoot"
    tagStr (Tbody_48 _ _) = "tbody"
    tagStr (Colgroup_48 _ _) = "colgroup"
    tagStr (Col_48 _) = "col"
    tagStr (Tr_48 _ _) = "tr"
instance TagStr Ent49 where
    tagStr (Tr_49 _ _) = "tr"
instance TagStr Ent50 where
    tagStr (Col_50 _) = "col"
instance TagStr Ent51 where
    tagStr (Th_51 _ _) = "th"
    tagStr (Td_51 _ _) = "td"
instance TagStr Ent52 where
    tagStr (Script_52 _ _) = "script"
    tagStr (Noscript_52 _ _) = "noscript"
    tagStr (Div_52 _ _) = "div"
    tagStr (P_52 _ _) = "p"
    tagStr (H1_52 _ _) = "h1"
    tagStr (H2_52 _ _) = "h2"
    tagStr (H3_52 _ _) = "h3"
    tagStr (H4_52 _ _) = "h4"
    tagStr (H5_52 _ _) = "h5"
    tagStr (H6_52 _ _) = "h6"
    tagStr (Ul_52 _ _) = "ul"
    tagStr (Ol_52 _ _) = "ol"
    tagStr (Dl_52 _ _) = "dl"
    tagStr (Address_52 _ _) = "address"
    tagStr (Hr_52 _) = "hr"
    tagStr (Pre_52 _ _) = "pre"
    tagStr (Blockquote_52 _ _) = "blockquote"
    tagStr (Ins_52 _ _) = "ins"
    tagStr (Del_52 _ _) = "del"
    tagStr (Span_52 _ _) = "span"
    tagStr (Bdo_52 _ _) = "bdo"
    tagStr (Br_52 _) = "br"
    tagStr (Em_52 _ _) = "em"
    tagStr (Strong_52 _ _) = "strong"
    tagStr (Dfn_52 _ _) = "dfn"
    tagStr (Code_52 _ _) = "code"
    tagStr (Samp_52 _ _) = "samp"
    tagStr (Kbd_52 _ _) = "kbd"
    tagStr (Var_52 _ _) = "var"
    tagStr (Cite_52 _ _) = "cite"
    tagStr (Abbr_52 _ _) = "abbr"
    tagStr (Acronym_52 _ _) = "acronym"
    tagStr (Q_52 _ _) = "q"
    tagStr (Sub_52 _ _) = "sub"
    tagStr (Sup_52 _ _) = "sup"
    tagStr (Tt_52 _ _) = "tt"
    tagStr (I_52 _ _) = "i"
    tagStr (B_52 _ _) = "b"
    tagStr (Big_52 _ _) = "big"
    tagStr (Small_52 _ _) = "small"
    tagStr (Object_52 _ _) = "object"
    tagStr (Param_52 _) = "param"
    tagStr (Img_52 _) = "img"
    tagStr (Map_52 _ _) = "map"
    tagStr (Form_52 _ _) = "form"
    tagStr (Input_52 _) = "input"
    tagStr (Select_52 _ _) = "select"
    tagStr (Textarea_52 _ _) = "textarea"
    tagStr (Fieldset_52 _ _) = "fieldset"
    tagStr (Button_52 _ _) = "button"
    tagStr (Table_52 _ _) = "table"
    tagStr (PCDATA_52 _ _) = "pcdata"
instance TagStr Ent53 where
    tagStr (Script_53 _ _) = "script"
    tagStr (Noscript_53 _ _) = "noscript"
    tagStr (Div_53 _ _) = "div"
    tagStr (P_53 _ _) = "p"
    tagStr (H1_53 _ _) = "h1"
    tagStr (H2_53 _ _) = "h2"
    tagStr (H3_53 _ _) = "h3"
    tagStr (H4_53 _ _) = "h4"
    tagStr (H5_53 _ _) = "h5"
    tagStr (H6_53 _ _) = "h6"
    tagStr (Ul_53 _ _) = "ul"
    tagStr (Ol_53 _ _) = "ol"
    tagStr (Dl_53 _ _) = "dl"
    tagStr (Address_53 _ _) = "address"
    tagStr (Hr_53 _) = "hr"
    tagStr (Pre_53 _ _) = "pre"
    tagStr (Blockquote_53 _ _) = "blockquote"
    tagStr (Ins_53 _ _) = "ins"
    tagStr (Del_53 _ _) = "del"
    tagStr (Area_53 _) = "area"
    tagStr (Form_53 _ _) = "form"
    tagStr (Fieldset_53 _ _) = "fieldset"
    tagStr (Table_53 _ _) = "table"
instance TagStr Ent54 where
    tagStr (Optgroup_54 _ _) = "optgroup"
    tagStr (Option_54 _ _) = "option"
instance TagStr Ent55 where
    tagStr (Option_55 _ _) = "option"
instance TagStr Ent56 where
    tagStr (Script_56 _ _) = "script"
    tagStr (Noscript_56 _ _) = "noscript"
    tagStr (Div_56 _ _) = "div"
    tagStr (P_56 _ _) = "p"
    tagStr (H1_56 _ _) = "h1"
    tagStr (H2_56 _ _) = "h2"
    tagStr (H3_56 _ _) = "h3"
    tagStr (H4_56 _ _) = "h4"
    tagStr (H5_56 _ _) = "h5"
    tagStr (H6_56 _ _) = "h6"
    tagStr (Ul_56 _ _) = "ul"
    tagStr (Ol_56 _ _) = "ol"
    tagStr (Dl_56 _ _) = "dl"
    tagStr (Address_56 _ _) = "address"
    tagStr (Hr_56 _) = "hr"
    tagStr (Pre_56 _ _) = "pre"
    tagStr (Blockquote_56 _ _) = "blockquote"
    tagStr (Ins_56 _ _) = "ins"
    tagStr (Del_56 _ _) = "del"
    tagStr (Span_56 _ _) = "span"
    tagStr (Bdo_56 _ _) = "bdo"
    tagStr (Br_56 _) = "br"
    tagStr (Em_56 _ _) = "em"
    tagStr (Strong_56 _ _) = "strong"
    tagStr (Dfn_56 _ _) = "dfn"
    tagStr (Code_56 _ _) = "code"
    tagStr (Samp_56 _ _) = "samp"
    tagStr (Kbd_56 _ _) = "kbd"
    tagStr (Var_56 _ _) = "var"
    tagStr (Cite_56 _ _) = "cite"
    tagStr (Abbr_56 _ _) = "abbr"
    tagStr (Acronym_56 _ _) = "acronym"
    tagStr (Q_56 _ _) = "q"
    tagStr (Sub_56 _ _) = "sub"
    tagStr (Sup_56 _ _) = "sup"
    tagStr (Tt_56 _ _) = "tt"
    tagStr (I_56 _ _) = "i"
    tagStr (B_56 _ _) = "b"
    tagStr (Big_56 _ _) = "big"
    tagStr (Small_56 _ _) = "small"
    tagStr (Object_56 _ _) = "object"
    tagStr (Img_56 _) = "img"
    tagStr (Map_56 _ _) = "map"
    tagStr (Table_56 _ _) = "table"
    tagStr (PCDATA_56 _ _) = "pcdata"
instance TagStr Ent57 where
    tagStr (Optgroup_57 _ _) = "optgroup"
    tagStr (Option_57 _ _) = "option"
instance TagStr Ent58 where
    tagStr (Option_58 _ _) = "option"
instance TagStr Ent59 where
    tagStr (Script_59 _ _) = "script"
    tagStr (Noscript_59 _ _) = "noscript"
    tagStr (Div_59 _ _) = "div"
    tagStr (P_59 _ _) = "p"
    tagStr (H1_59 _ _) = "h1"
    tagStr (H2_59 _ _) = "h2"
    tagStr (H3_59 _ _) = "h3"
    tagStr (H4_59 _ _) = "h4"
    tagStr (H5_59 _ _) = "h5"
    tagStr (H6_59 _ _) = "h6"
    tagStr (Ul_59 _ _) = "ul"
    tagStr (Ol_59 _ _) = "ol"
    tagStr (Dl_59 _ _) = "dl"
    tagStr (Address_59 _ _) = "address"
    tagStr (Hr_59 _) = "hr"
    tagStr (Pre_59 _ _) = "pre"
    tagStr (Blockquote_59 _ _) = "blockquote"
    tagStr (Ins_59 _ _) = "ins"
    tagStr (Del_59 _ _) = "del"
    tagStr (Span_59 _ _) = "span"
    tagStr (Bdo_59 _ _) = "bdo"
    tagStr (Br_59 _) = "br"
    tagStr (Em_59 _ _) = "em"
    tagStr (Strong_59 _ _) = "strong"
    tagStr (Dfn_59 _ _) = "dfn"
    tagStr (Code_59 _ _) = "code"
    tagStr (Samp_59 _ _) = "samp"
    tagStr (Kbd_59 _ _) = "kbd"
    tagStr (Var_59 _ _) = "var"
    tagStr (Cite_59 _ _) = "cite"
    tagStr (Abbr_59 _ _) = "abbr"
    tagStr (Acronym_59 _ _) = "acronym"
    tagStr (Q_59 _ _) = "q"
    tagStr (Sub_59 _ _) = "sub"
    tagStr (Sup_59 _ _) = "sup"
    tagStr (Tt_59 _ _) = "tt"
    tagStr (I_59 _ _) = "i"
    tagStr (B_59 _ _) = "b"
    tagStr (Big_59 _ _) = "big"
    tagStr (Small_59 _ _) = "small"
    tagStr (Object_59 _ _) = "object"
    tagStr (Img_59 _) = "img"
    tagStr (Map_59 _ _) = "map"
    tagStr (Table_59 _ _) = "table"
    tagStr (PCDATA_59 _ _) = "pcdata"
instance TagStr Ent60 where
    tagStr (Script_60 _ _) = "script"
    tagStr (Ins_60 _ _) = "ins"
    tagStr (Del_60 _ _) = "del"
    tagStr (A_60 _ _) = "a"
    tagStr (Span_60 _ _) = "span"
    tagStr (Bdo_60 _ _) = "bdo"
    tagStr (Br_60 _) = "br"
    tagStr (Em_60 _ _) = "em"
    tagStr (Strong_60 _ _) = "strong"
    tagStr (Dfn_60 _ _) = "dfn"
    tagStr (Code_60 _ _) = "code"
    tagStr (Samp_60 _ _) = "samp"
    tagStr (Kbd_60 _ _) = "kbd"
    tagStr (Var_60 _ _) = "var"
    tagStr (Cite_60 _ _) = "cite"
    tagStr (Abbr_60 _ _) = "abbr"
    tagStr (Acronym_60 _ _) = "acronym"
    tagStr (Q_60 _ _) = "q"
    tagStr (Sub_60 _ _) = "sub"
    tagStr (Sup_60 _ _) = "sup"
    tagStr (Tt_60 _ _) = "tt"
    tagStr (I_60 _ _) = "i"
    tagStr (B_60 _ _) = "b"
    tagStr (Big_60 _ _) = "big"
    tagStr (Small_60 _ _) = "small"
    tagStr (Object_60 _ _) = "object"
    tagStr (Img_60 _) = "img"
    tagStr (Map_60 _ _) = "map"
    tagStr (Label_60 _ _) = "label"
    tagStr (Input_60 _) = "input"
    tagStr (Select_60 _ _) = "select"
    tagStr (Textarea_60 _ _) = "textarea"
    tagStr (Button_60 _ _) = "button"
    tagStr (PCDATA_60 _ _) = "pcdata"
instance TagStr Ent61 where
    tagStr (Script_61 _ _) = "script"
    tagStr (Noscript_61 _ _) = "noscript"
    tagStr (Div_61 _ _) = "div"
    tagStr (P_61 _ _) = "p"
    tagStr (H1_61 _ _) = "h1"
    tagStr (H2_61 _ _) = "h2"
    tagStr (H3_61 _ _) = "h3"
    tagStr (H4_61 _ _) = "h4"
    tagStr (H5_61 _ _) = "h5"
    tagStr (H6_61 _ _) = "h6"
    tagStr (Ul_61 _ _) = "ul"
    tagStr (Ol_61 _ _) = "ol"
    tagStr (Dl_61 _ _) = "dl"
    tagStr (Address_61 _ _) = "address"
    tagStr (Hr_61 _) = "hr"
    tagStr (Pre_61 _ _) = "pre"
    tagStr (Blockquote_61 _ _) = "blockquote"
    tagStr (Ins_61 _ _) = "ins"
    tagStr (Del_61 _ _) = "del"
    tagStr (Area_61 _) = "area"
    tagStr (Form_61 _ _) = "form"
    tagStr (Fieldset_61 _ _) = "fieldset"
    tagStr (Table_61 _ _) = "table"
instance TagStr Ent62 where
    tagStr (Script_62 _ _) = "script"
    tagStr (Ins_62 _ _) = "ins"
    tagStr (Del_62 _ _) = "del"
    tagStr (A_62 _ _) = "a"
    tagStr (Span_62 _ _) = "span"
    tagStr (Bdo_62 _ _) = "bdo"
    tagStr (Br_62 _) = "br"
    tagStr (Em_62 _ _) = "em"
    tagStr (Strong_62 _ _) = "strong"
    tagStr (Dfn_62 _ _) = "dfn"
    tagStr (Code_62 _ _) = "code"
    tagStr (Samp_62 _ _) = "samp"
    tagStr (Kbd_62 _ _) = "kbd"
    tagStr (Var_62 _ _) = "var"
    tagStr (Cite_62 _ _) = "cite"
    tagStr (Abbr_62 _ _) = "abbr"
    tagStr (Acronym_62 _ _) = "acronym"
    tagStr (Q_62 _ _) = "q"
    tagStr (Sub_62 _ _) = "sub"
    tagStr (Sup_62 _ _) = "sup"
    tagStr (Tt_62 _ _) = "tt"
    tagStr (I_62 _ _) = "i"
    tagStr (B_62 _ _) = "b"
    tagStr (Big_62 _ _) = "big"
    tagStr (Small_62 _ _) = "small"
    tagStr (Object_62 _ _) = "object"
    tagStr (Img_62 _) = "img"
    tagStr (Map_62 _ _) = "map"
    tagStr (Input_62 _) = "input"
    tagStr (Select_62 _ _) = "select"
    tagStr (Textarea_62 _ _) = "textarea"
    tagStr (Button_62 _ _) = "button"
    tagStr (PCDATA_62 _ _) = "pcdata"
instance TagStr Ent63 where
    tagStr (PCDATA_63 _ _) = "pcdata"
instance TagStr Ent64 where
    tagStr (Script_64 _ _) = "script"
    tagStr (Noscript_64 _ _) = "noscript"
    tagStr (Div_64 _ _) = "div"
    tagStr (P_64 _ _) = "p"
    tagStr (H1_64 _ _) = "h1"
    tagStr (H2_64 _ _) = "h2"
    tagStr (H3_64 _ _) = "h3"
    tagStr (H4_64 _ _) = "h4"
    tagStr (H5_64 _ _) = "h5"
    tagStr (H6_64 _ _) = "h6"
    tagStr (Ul_64 _ _) = "ul"
    tagStr (Ol_64 _ _) = "ol"
    tagStr (Dl_64 _ _) = "dl"
    tagStr (Address_64 _ _) = "address"
    tagStr (Hr_64 _) = "hr"
    tagStr (Pre_64 _ _) = "pre"
    tagStr (Blockquote_64 _ _) = "blockquote"
    tagStr (Ins_64 _ _) = "ins"
    tagStr (Del_64 _ _) = "del"
    tagStr (A_64 _ _) = "a"
    tagStr (Span_64 _ _) = "span"
    tagStr (Bdo_64 _ _) = "bdo"
    tagStr (Br_64 _) = "br"
    tagStr (Em_64 _ _) = "em"
    tagStr (Strong_64 _ _) = "strong"
    tagStr (Dfn_64 _ _) = "dfn"
    tagStr (Code_64 _ _) = "code"
    tagStr (Samp_64 _ _) = "samp"
    tagStr (Kbd_64 _ _) = "kbd"
    tagStr (Var_64 _ _) = "var"
    tagStr (Cite_64 _ _) = "cite"
    tagStr (Abbr_64 _ _) = "abbr"
    tagStr (Acronym_64 _ _) = "acronym"
    tagStr (Q_64 _ _) = "q"
    tagStr (Sub_64 _ _) = "sub"
    tagStr (Sup_64 _ _) = "sup"
    tagStr (Tt_64 _ _) = "tt"
    tagStr (I_64 _ _) = "i"
    tagStr (B_64 _ _) = "b"
    tagStr (Big_64 _ _) = "big"
    tagStr (Small_64 _ _) = "small"
    tagStr (Object_64 _ _) = "object"
    tagStr (Img_64 _) = "img"
    tagStr (Map_64 _ _) = "map"
    tagStr (Form_64 _ _) = "form"
    tagStr (Input_64 _) = "input"
    tagStr (Select_64 _ _) = "select"
    tagStr (Textarea_64 _ _) = "textarea"
    tagStr (Fieldset_64 _ _) = "fieldset"
    tagStr (Button_64 _ _) = "button"
    tagStr (Table_64 _ _) = "table"
    tagStr (PCDATA_64 _ _) = "pcdata"
instance TagStr Ent65 where
    tagStr (Script_65 _ _) = "script"
    tagStr (Noscript_65 _ _) = "noscript"
    tagStr (Div_65 _ _) = "div"
    tagStr (P_65 _ _) = "p"
    tagStr (H1_65 _ _) = "h1"
    tagStr (H2_65 _ _) = "h2"
    tagStr (H3_65 _ _) = "h3"
    tagStr (H4_65 _ _) = "h4"
    tagStr (H5_65 _ _) = "h5"
    tagStr (H6_65 _ _) = "h6"
    tagStr (Ul_65 _ _) = "ul"
    tagStr (Ol_65 _ _) = "ol"
    tagStr (Dl_65 _ _) = "dl"
    tagStr (Address_65 _ _) = "address"
    tagStr (Hr_65 _) = "hr"
    tagStr (Pre_65 _ _) = "pre"
    tagStr (Blockquote_65 _ _) = "blockquote"
    tagStr (Ins_65 _ _) = "ins"
    tagStr (Del_65 _ _) = "del"
    tagStr (Form_65 _ _) = "form"
    tagStr (Fieldset_65 _ _) = "fieldset"
    tagStr (Table_65 _ _) = "table"
instance TagStr Ent66 where
    tagStr (Li_66 _ _) = "li"
instance TagStr Ent67 where
    tagStr (Dt_67 _ _) = "dt"
    tagStr (Dd_67 _ _) = "dd"
instance TagStr Ent68 where
    tagStr (Script_68 _ _) = "script"
    tagStr (Ins_68 _ _) = "ins"
    tagStr (Del_68 _ _) = "del"
    tagStr (A_68 _ _) = "a"
    tagStr (Span_68 _ _) = "span"
    tagStr (Bdo_68 _ _) = "bdo"
    tagStr (Br_68 _) = "br"
    tagStr (Em_68 _ _) = "em"
    tagStr (Strong_68 _ _) = "strong"
    tagStr (Dfn_68 _ _) = "dfn"
    tagStr (Code_68 _ _) = "code"
    tagStr (Samp_68 _ _) = "samp"
    tagStr (Kbd_68 _ _) = "kbd"
    tagStr (Var_68 _ _) = "var"
    tagStr (Cite_68 _ _) = "cite"
    tagStr (Abbr_68 _ _) = "abbr"
    tagStr (Acronym_68 _ _) = "acronym"
    tagStr (Q_68 _ _) = "q"
    tagStr (Sub_68 _ _) = "sub"
    tagStr (Sup_68 _ _) = "sup"
    tagStr (Tt_68 _ _) = "tt"
    tagStr (I_68 _ _) = "i"
    tagStr (B_68 _ _) = "b"
    tagStr (Big_68 _ _) = "big"
    tagStr (Small_68 _ _) = "small"
    tagStr (Map_68 _ _) = "map"
    tagStr (Input_68 _) = "input"
    tagStr (Select_68 _ _) = "select"
    tagStr (Textarea_68 _ _) = "textarea"
    tagStr (Button_68 _ _) = "button"
    tagStr (PCDATA_68 _ _) = "pcdata"
instance TagStr Ent69 where
    tagStr (Script_69 _ _) = "script"
    tagStr (Noscript_69 _ _) = "noscript"
    tagStr (Div_69 _ _) = "div"
    tagStr (P_69 _ _) = "p"
    tagStr (H1_69 _ _) = "h1"
    tagStr (H2_69 _ _) = "h2"
    tagStr (H3_69 _ _) = "h3"
    tagStr (H4_69 _ _) = "h4"
    tagStr (H5_69 _ _) = "h5"
    tagStr (H6_69 _ _) = "h6"
    tagStr (Ul_69 _ _) = "ul"
    tagStr (Ol_69 _ _) = "ol"
    tagStr (Dl_69 _ _) = "dl"
    tagStr (Address_69 _ _) = "address"
    tagStr (Hr_69 _) = "hr"
    tagStr (Pre_69 _ _) = "pre"
    tagStr (Blockquote_69 _ _) = "blockquote"
    tagStr (Ins_69 _ _) = "ins"
    tagStr (Del_69 _ _) = "del"
    tagStr (Fieldset_69 _ _) = "fieldset"
    tagStr (Table_69 _ _) = "table"
instance TagStr Ent70 where
    tagStr (Script_70 _ _) = "script"
    tagStr (Noscript_70 _ _) = "noscript"
    tagStr (Div_70 _ _) = "div"
    tagStr (P_70 _ _) = "p"
    tagStr (H1_70 _ _) = "h1"
    tagStr (H2_70 _ _) = "h2"
    tagStr (H3_70 _ _) = "h3"
    tagStr (H4_70 _ _) = "h4"
    tagStr (H5_70 _ _) = "h5"
    tagStr (H6_70 _ _) = "h6"
    tagStr (Ul_70 _ _) = "ul"
    tagStr (Ol_70 _ _) = "ol"
    tagStr (Dl_70 _ _) = "dl"
    tagStr (Address_70 _ _) = "address"
    tagStr (Hr_70 _) = "hr"
    tagStr (Pre_70 _ _) = "pre"
    tagStr (Blockquote_70 _ _) = "blockquote"
    tagStr (Ins_70 _ _) = "ins"
    tagStr (Del_70 _ _) = "del"
    tagStr (A_70 _ _) = "a"
    tagStr (Span_70 _ _) = "span"
    tagStr (Bdo_70 _ _) = "bdo"
    tagStr (Br_70 _) = "br"
    tagStr (Em_70 _ _) = "em"
    tagStr (Strong_70 _ _) = "strong"
    tagStr (Dfn_70 _ _) = "dfn"
    tagStr (Code_70 _ _) = "code"
    tagStr (Samp_70 _ _) = "samp"
    tagStr (Kbd_70 _ _) = "kbd"
    tagStr (Var_70 _ _) = "var"
    tagStr (Cite_70 _ _) = "cite"
    tagStr (Abbr_70 _ _) = "abbr"
    tagStr (Acronym_70 _ _) = "acronym"
    tagStr (Q_70 _ _) = "q"
    tagStr (Sub_70 _ _) = "sub"
    tagStr (Sup_70 _ _) = "sup"
    tagStr (Tt_70 _ _) = "tt"
    tagStr (I_70 _ _) = "i"
    tagStr (B_70 _ _) = "b"
    tagStr (Big_70 _ _) = "big"
    tagStr (Small_70 _ _) = "small"
    tagStr (Object_70 _ _) = "object"
    tagStr (Img_70 _) = "img"
    tagStr (Map_70 _ _) = "map"
    tagStr (Input_70 _) = "input"
    tagStr (Select_70 _ _) = "select"
    tagStr (Textarea_70 _ _) = "textarea"
    tagStr (Fieldset_70 _ _) = "fieldset"
    tagStr (Button_70 _ _) = "button"
    tagStr (Table_70 _ _) = "table"
    tagStr (PCDATA_70 _ _) = "pcdata"
instance TagStr Ent71 where
    tagStr (Script_71 _ _) = "script"
    tagStr (Ins_71 _ _) = "ins"
    tagStr (Del_71 _ _) = "del"
    tagStr (A_71 _ _) = "a"
    tagStr (Span_71 _ _) = "span"
    tagStr (Bdo_71 _ _) = "bdo"
    tagStr (Br_71 _) = "br"
    tagStr (Em_71 _ _) = "em"
    tagStr (Strong_71 _ _) = "strong"
    tagStr (Dfn_71 _ _) = "dfn"
    tagStr (Code_71 _ _) = "code"
    tagStr (Samp_71 _ _) = "samp"
    tagStr (Kbd_71 _ _) = "kbd"
    tagStr (Var_71 _ _) = "var"
    tagStr (Cite_71 _ _) = "cite"
    tagStr (Abbr_71 _ _) = "abbr"
    tagStr (Acronym_71 _ _) = "acronym"
    tagStr (Q_71 _ _) = "q"
    tagStr (Sub_71 _ _) = "sub"
    tagStr (Sup_71 _ _) = "sup"
    tagStr (Tt_71 _ _) = "tt"
    tagStr (I_71 _ _) = "i"
    tagStr (B_71 _ _) = "b"
    tagStr (Big_71 _ _) = "big"
    tagStr (Small_71 _ _) = "small"
    tagStr (Object_71 _ _) = "object"
    tagStr (Img_71 _) = "img"
    tagStr (Map_71 _ _) = "map"
    tagStr (Input_71 _) = "input"
    tagStr (Select_71 _ _) = "select"
    tagStr (Textarea_71 _ _) = "textarea"
    tagStr (Button_71 _ _) = "button"
    tagStr (PCDATA_71 _ _) = "pcdata"
instance TagStr Ent72 where
    tagStr (Li_72 _ _) = "li"
instance TagStr Ent73 where
    tagStr (Dt_73 _ _) = "dt"
    tagStr (Dd_73 _ _) = "dd"
instance TagStr Ent74 where
    tagStr (Script_74 _ _) = "script"
    tagStr (Ins_74 _ _) = "ins"
    tagStr (Del_74 _ _) = "del"
    tagStr (A_74 _ _) = "a"
    tagStr (Span_74 _ _) = "span"
    tagStr (Bdo_74 _ _) = "bdo"
    tagStr (Br_74 _) = "br"
    tagStr (Em_74 _ _) = "em"
    tagStr (Strong_74 _ _) = "strong"
    tagStr (Dfn_74 _ _) = "dfn"
    tagStr (Code_74 _ _) = "code"
    tagStr (Samp_74 _ _) = "samp"
    tagStr (Kbd_74 _ _) = "kbd"
    tagStr (Var_74 _ _) = "var"
    tagStr (Cite_74 _ _) = "cite"
    tagStr (Abbr_74 _ _) = "abbr"
    tagStr (Acronym_74 _ _) = "acronym"
    tagStr (Q_74 _ _) = "q"
    tagStr (Sub_74 _ _) = "sub"
    tagStr (Sup_74 _ _) = "sup"
    tagStr (Tt_74 _ _) = "tt"
    tagStr (I_74 _ _) = "i"
    tagStr (B_74 _ _) = "b"
    tagStr (Big_74 _ _) = "big"
    tagStr (Small_74 _ _) = "small"
    tagStr (Map_74 _ _) = "map"
    tagStr (Input_74 _) = "input"
    tagStr (Select_74 _ _) = "select"
    tagStr (Textarea_74 _ _) = "textarea"
    tagStr (Button_74 _ _) = "button"
    tagStr (PCDATA_74 _ _) = "pcdata"
instance TagStr Ent75 where
    tagStr (Script_75 _ _) = "script"
    tagStr (Noscript_75 _ _) = "noscript"
    tagStr (Div_75 _ _) = "div"
    tagStr (P_75 _ _) = "p"
    tagStr (H1_75 _ _) = "h1"
    tagStr (H2_75 _ _) = "h2"
    tagStr (H3_75 _ _) = "h3"
    tagStr (H4_75 _ _) = "h4"
    tagStr (H5_75 _ _) = "h5"
    tagStr (H6_75 _ _) = "h6"
    tagStr (Ul_75 _ _) = "ul"
    tagStr (Ol_75 _ _) = "ol"
    tagStr (Dl_75 _ _) = "dl"
    tagStr (Address_75 _ _) = "address"
    tagStr (Hr_75 _) = "hr"
    tagStr (Pre_75 _ _) = "pre"
    tagStr (Blockquote_75 _ _) = "blockquote"
    tagStr (Ins_75 _ _) = "ins"
    tagStr (Del_75 _ _) = "del"
    tagStr (A_75 _ _) = "a"
    tagStr (Span_75 _ _) = "span"
    tagStr (Bdo_75 _ _) = "bdo"
    tagStr (Br_75 _) = "br"
    tagStr (Em_75 _ _) = "em"
    tagStr (Strong_75 _ _) = "strong"
    tagStr (Dfn_75 _ _) = "dfn"
    tagStr (Code_75 _ _) = "code"
    tagStr (Samp_75 _ _) = "samp"
    tagStr (Kbd_75 _ _) = "kbd"
    tagStr (Var_75 _ _) = "var"
    tagStr (Cite_75 _ _) = "cite"
    tagStr (Abbr_75 _ _) = "abbr"
    tagStr (Acronym_75 _ _) = "acronym"
    tagStr (Q_75 _ _) = "q"
    tagStr (Sub_75 _ _) = "sub"
    tagStr (Sup_75 _ _) = "sup"
    tagStr (Tt_75 _ _) = "tt"
    tagStr (I_75 _ _) = "i"
    tagStr (B_75 _ _) = "b"
    tagStr (Big_75 _ _) = "big"
    tagStr (Small_75 _ _) = "small"
    tagStr (Object_75 _ _) = "object"
    tagStr (Img_75 _) = "img"
    tagStr (Map_75 _ _) = "map"
    tagStr (Input_75 _) = "input"
    tagStr (Select_75 _ _) = "select"
    tagStr (Textarea_75 _ _) = "textarea"
    tagStr (Fieldset_75 _ _) = "fieldset"
    tagStr (Legend_75 _ _) = "legend"
    tagStr (Button_75 _ _) = "button"
    tagStr (Table_75 _ _) = "table"
    tagStr (PCDATA_75 _ _) = "pcdata"
instance TagStr Ent76 where
    tagStr (Caption_76 _ _) = "caption"
    tagStr (Thead_76 _ _) = "thead"
    tagStr (Tfoot_76 _ _) = "tfoot"
    tagStr (Tbody_76 _ _) = "tbody"
    tagStr (Colgroup_76 _ _) = "colgroup"
    tagStr (Col_76 _) = "col"
    tagStr (Tr_76 _ _) = "tr"
instance TagStr Ent77 where
    tagStr (Tr_77 _ _) = "tr"
instance TagStr Ent78 where
    tagStr (Col_78 _) = "col"
instance TagStr Ent79 where
    tagStr (Th_79 _ _) = "th"
    tagStr (Td_79 _ _) = "td"
instance TagStr Ent80 where
    tagStr (Script_80 _ _) = "script"
    tagStr (Noscript_80 _ _) = "noscript"
    tagStr (Div_80 _ _) = "div"
    tagStr (P_80 _ _) = "p"
    tagStr (H1_80 _ _) = "h1"
    tagStr (H2_80 _ _) = "h2"
    tagStr (H3_80 _ _) = "h3"
    tagStr (H4_80 _ _) = "h4"
    tagStr (H5_80 _ _) = "h5"
    tagStr (H6_80 _ _) = "h6"
    tagStr (Ul_80 _ _) = "ul"
    tagStr (Ol_80 _ _) = "ol"
    tagStr (Dl_80 _ _) = "dl"
    tagStr (Address_80 _ _) = "address"
    tagStr (Hr_80 _) = "hr"
    tagStr (Pre_80 _ _) = "pre"
    tagStr (Blockquote_80 _ _) = "blockquote"
    tagStr (Ins_80 _ _) = "ins"
    tagStr (Del_80 _ _) = "del"
    tagStr (A_80 _ _) = "a"
    tagStr (Span_80 _ _) = "span"
    tagStr (Bdo_80 _ _) = "bdo"
    tagStr (Br_80 _) = "br"
    tagStr (Em_80 _ _) = "em"
    tagStr (Strong_80 _ _) = "strong"
    tagStr (Dfn_80 _ _) = "dfn"
    tagStr (Code_80 _ _) = "code"
    tagStr (Samp_80 _ _) = "samp"
    tagStr (Kbd_80 _ _) = "kbd"
    tagStr (Var_80 _ _) = "var"
    tagStr (Cite_80 _ _) = "cite"
    tagStr (Abbr_80 _ _) = "abbr"
    tagStr (Acronym_80 _ _) = "acronym"
    tagStr (Q_80 _ _) = "q"
    tagStr (Sub_80 _ _) = "sub"
    tagStr (Sup_80 _ _) = "sup"
    tagStr (Tt_80 _ _) = "tt"
    tagStr (I_80 _ _) = "i"
    tagStr (B_80 _ _) = "b"
    tagStr (Big_80 _ _) = "big"
    tagStr (Small_80 _ _) = "small"
    tagStr (Object_80 _ _) = "object"
    tagStr (Img_80 _) = "img"
    tagStr (Map_80 _ _) = "map"
    tagStr (Form_80 _ _) = "form"
    tagStr (Input_80 _) = "input"
    tagStr (Select_80 _ _) = "select"
    tagStr (Textarea_80 _ _) = "textarea"
    tagStr (Fieldset_80 _ _) = "fieldset"
    tagStr (Legend_80 _ _) = "legend"
    tagStr (Button_80 _ _) = "button"
    tagStr (Table_80 _ _) = "table"
    tagStr (PCDATA_80 _ _) = "pcdata"
instance TagStr Ent81 where
    tagStr (Caption_81 _ _) = "caption"
    tagStr (Thead_81 _ _) = "thead"
    tagStr (Tfoot_81 _ _) = "tfoot"
    tagStr (Tbody_81 _ _) = "tbody"
    tagStr (Colgroup_81 _ _) = "colgroup"
    tagStr (Col_81 _) = "col"
    tagStr (Tr_81 _ _) = "tr"
instance TagStr Ent82 where
    tagStr (Tr_82 _ _) = "tr"
instance TagStr Ent83 where
    tagStr (Col_83 _) = "col"
instance TagStr Ent84 where
    tagStr (Th_84 _ _) = "th"
    tagStr (Td_84 _ _) = "td"
instance TagStr Ent85 where
    tagStr (Script_85 _ _) = "script"
    tagStr (Noscript_85 _ _) = "noscript"
    tagStr (Div_85 _ _) = "div"
    tagStr (P_85 _ _) = "p"
    tagStr (H1_85 _ _) = "h1"
    tagStr (H2_85 _ _) = "h2"
    tagStr (H3_85 _ _) = "h3"
    tagStr (H4_85 _ _) = "h4"
    tagStr (H5_85 _ _) = "h5"
    tagStr (H6_85 _ _) = "h6"
    tagStr (Ul_85 _ _) = "ul"
    tagStr (Ol_85 _ _) = "ol"
    tagStr (Dl_85 _ _) = "dl"
    tagStr (Address_85 _ _) = "address"
    tagStr (Hr_85 _) = "hr"
    tagStr (Pre_85 _ _) = "pre"
    tagStr (Blockquote_85 _ _) = "blockquote"
    tagStr (Ins_85 _ _) = "ins"
    tagStr (Del_85 _ _) = "del"
    tagStr (A_85 _ _) = "a"
    tagStr (Span_85 _ _) = "span"
    tagStr (Bdo_85 _ _) = "bdo"
    tagStr (Br_85 _) = "br"
    tagStr (Em_85 _ _) = "em"
    tagStr (Strong_85 _ _) = "strong"
    tagStr (Dfn_85 _ _) = "dfn"
    tagStr (Code_85 _ _) = "code"
    tagStr (Samp_85 _ _) = "samp"
    tagStr (Kbd_85 _ _) = "kbd"
    tagStr (Var_85 _ _) = "var"
    tagStr (Cite_85 _ _) = "cite"
    tagStr (Abbr_85 _ _) = "abbr"
    tagStr (Acronym_85 _ _) = "acronym"
    tagStr (Q_85 _ _) = "q"
    tagStr (Sub_85 _ _) = "sub"
    tagStr (Sup_85 _ _) = "sup"
    tagStr (Tt_85 _ _) = "tt"
    tagStr (I_85 _ _) = "i"
    tagStr (B_85 _ _) = "b"
    tagStr (Big_85 _ _) = "big"
    tagStr (Small_85 _ _) = "small"
    tagStr (Object_85 _ _) = "object"
    tagStr (Param_85 _) = "param"
    tagStr (Img_85 _) = "img"
    tagStr (Map_85 _ _) = "map"
    tagStr (Form_85 _ _) = "form"
    tagStr (Input_85 _) = "input"
    tagStr (Select_85 _ _) = "select"
    tagStr (Textarea_85 _ _) = "textarea"
    tagStr (Fieldset_85 _ _) = "fieldset"
    tagStr (Button_85 _ _) = "button"
    tagStr (Table_85 _ _) = "table"
    tagStr (PCDATA_85 _ _) = "pcdata"
instance TagStr Ent86 where
    tagStr (Script_86 _ _) = "script"
    tagStr (Noscript_86 _ _) = "noscript"
    tagStr (Div_86 _ _) = "div"
    tagStr (P_86 _ _) = "p"
    tagStr (H1_86 _ _) = "h1"
    tagStr (H2_86 _ _) = "h2"
    tagStr (H3_86 _ _) = "h3"
    tagStr (H4_86 _ _) = "h4"
    tagStr (H5_86 _ _) = "h5"
    tagStr (H6_86 _ _) = "h6"
    tagStr (Ul_86 _ _) = "ul"
    tagStr (Ol_86 _ _) = "ol"
    tagStr (Dl_86 _ _) = "dl"
    tagStr (Address_86 _ _) = "address"
    tagStr (Hr_86 _) = "hr"
    tagStr (Pre_86 _ _) = "pre"
    tagStr (Blockquote_86 _ _) = "blockquote"
    tagStr (Ins_86 _ _) = "ins"
    tagStr (Del_86 _ _) = "del"
    tagStr (Area_86 _) = "area"
    tagStr (Form_86 _ _) = "form"
    tagStr (Fieldset_86 _ _) = "fieldset"
    tagStr (Table_86 _ _) = "table"
instance TagStr Ent87 where
    tagStr (Optgroup_87 _ _) = "optgroup"
    tagStr (Option_87 _ _) = "option"
instance TagStr Ent88 where
    tagStr (Option_88 _ _) = "option"
instance TagStr Ent89 where
    tagStr (Script_89 _ _) = "script"
    tagStr (Noscript_89 _ _) = "noscript"
    tagStr (Div_89 _ _) = "div"
    tagStr (P_89 _ _) = "p"
    tagStr (H1_89 _ _) = "h1"
    tagStr (H2_89 _ _) = "h2"
    tagStr (H3_89 _ _) = "h3"
    tagStr (H4_89 _ _) = "h4"
    tagStr (H5_89 _ _) = "h5"
    tagStr (H6_89 _ _) = "h6"
    tagStr (Ul_89 _ _) = "ul"
    tagStr (Ol_89 _ _) = "ol"
    tagStr (Dl_89 _ _) = "dl"
    tagStr (Address_89 _ _) = "address"
    tagStr (Hr_89 _) = "hr"
    tagStr (Pre_89 _ _) = "pre"
    tagStr (Blockquote_89 _ _) = "blockquote"
    tagStr (Ins_89 _ _) = "ins"
    tagStr (Del_89 _ _) = "del"
    tagStr (Span_89 _ _) = "span"
    tagStr (Bdo_89 _ _) = "bdo"
    tagStr (Br_89 _) = "br"
    tagStr (Em_89 _ _) = "em"
    tagStr (Strong_89 _ _) = "strong"
    tagStr (Dfn_89 _ _) = "dfn"
    tagStr (Code_89 _ _) = "code"
    tagStr (Samp_89 _ _) = "samp"
    tagStr (Kbd_89 _ _) = "kbd"
    tagStr (Var_89 _ _) = "var"
    tagStr (Cite_89 _ _) = "cite"
    tagStr (Abbr_89 _ _) = "abbr"
    tagStr (Acronym_89 _ _) = "acronym"
    tagStr (Q_89 _ _) = "q"
    tagStr (Sub_89 _ _) = "sub"
    tagStr (Sup_89 _ _) = "sup"
    tagStr (Tt_89 _ _) = "tt"
    tagStr (I_89 _ _) = "i"
    tagStr (B_89 _ _) = "b"
    tagStr (Big_89 _ _) = "big"
    tagStr (Small_89 _ _) = "small"
    tagStr (Object_89 _ _) = "object"
    tagStr (Img_89 _) = "img"
    tagStr (Map_89 _ _) = "map"
    tagStr (Table_89 _ _) = "table"
    tagStr (PCDATA_89 _ _) = "pcdata"
instance TagStr Ent90 where
    tagStr (Optgroup_90 _ _) = "optgroup"
    tagStr (Option_90 _ _) = "option"
instance TagStr Ent91 where
    tagStr (Option_91 _ _) = "option"
instance TagStr Ent92 where
    tagStr (Script_92 _ _) = "script"
    tagStr (Noscript_92 _ _) = "noscript"
    tagStr (Div_92 _ _) = "div"
    tagStr (P_92 _ _) = "p"
    tagStr (H1_92 _ _) = "h1"
    tagStr (H2_92 _ _) = "h2"
    tagStr (H3_92 _ _) = "h3"
    tagStr (H4_92 _ _) = "h4"
    tagStr (H5_92 _ _) = "h5"
    tagStr (H6_92 _ _) = "h6"
    tagStr (Ul_92 _ _) = "ul"
    tagStr (Ol_92 _ _) = "ol"
    tagStr (Dl_92 _ _) = "dl"
    tagStr (Address_92 _ _) = "address"
    tagStr (Hr_92 _) = "hr"
    tagStr (Pre_92 _ _) = "pre"
    tagStr (Blockquote_92 _ _) = "blockquote"
    tagStr (Ins_92 _ _) = "ins"
    tagStr (Del_92 _ _) = "del"
    tagStr (Span_92 _ _) = "span"
    tagStr (Bdo_92 _ _) = "bdo"
    tagStr (Br_92 _) = "br"
    tagStr (Em_92 _ _) = "em"
    tagStr (Strong_92 _ _) = "strong"
    tagStr (Dfn_92 _ _) = "dfn"
    tagStr (Code_92 _ _) = "code"
    tagStr (Samp_92 _ _) = "samp"
    tagStr (Kbd_92 _ _) = "kbd"
    tagStr (Var_92 _ _) = "var"
    tagStr (Cite_92 _ _) = "cite"
    tagStr (Abbr_92 _ _) = "abbr"
    tagStr (Acronym_92 _ _) = "acronym"
    tagStr (Q_92 _ _) = "q"
    tagStr (Sub_92 _ _) = "sub"
    tagStr (Sup_92 _ _) = "sup"
    tagStr (Tt_92 _ _) = "tt"
    tagStr (I_92 _ _) = "i"
    tagStr (B_92 _ _) = "b"
    tagStr (Big_92 _ _) = "big"
    tagStr (Small_92 _ _) = "small"
    tagStr (Object_92 _ _) = "object"
    tagStr (Img_92 _) = "img"
    tagStr (Map_92 _ _) = "map"
    tagStr (Table_92 _ _) = "table"
    tagStr (PCDATA_92 _ _) = "pcdata"
instance TagStr Ent93 where
    tagStr (Script_93 _ _) = "script"
    tagStr (Noscript_93 _ _) = "noscript"
    tagStr (Div_93 _ _) = "div"
    tagStr (P_93 _ _) = "p"
    tagStr (H1_93 _ _) = "h1"
    tagStr (H2_93 _ _) = "h2"
    tagStr (H3_93 _ _) = "h3"
    tagStr (H4_93 _ _) = "h4"
    tagStr (H5_93 _ _) = "h5"
    tagStr (H6_93 _ _) = "h6"
    tagStr (Ul_93 _ _) = "ul"
    tagStr (Ol_93 _ _) = "ol"
    tagStr (Dl_93 _ _) = "dl"
    tagStr (Address_93 _ _) = "address"
    tagStr (Hr_93 _) = "hr"
    tagStr (Pre_93 _ _) = "pre"
    tagStr (Blockquote_93 _ _) = "blockquote"
    tagStr (Ins_93 _ _) = "ins"
    tagStr (Del_93 _ _) = "del"
    tagStr (Form_93 _ _) = "form"
    tagStr (Fieldset_93 _ _) = "fieldset"
    tagStr (Table_93 _ _) = "table"
instance TagStr Ent94 where
    tagStr (Script_94 _ _) = "script"
    tagStr (Noscript_94 _ _) = "noscript"
    tagStr (Div_94 _ _) = "div"
    tagStr (P_94 _ _) = "p"
    tagStr (H1_94 _ _) = "h1"
    tagStr (H2_94 _ _) = "h2"
    tagStr (H3_94 _ _) = "h3"
    tagStr (H4_94 _ _) = "h4"
    tagStr (H5_94 _ _) = "h5"
    tagStr (H6_94 _ _) = "h6"
    tagStr (Ul_94 _ _) = "ul"
    tagStr (Ol_94 _ _) = "ol"
    tagStr (Dl_94 _ _) = "dl"
    tagStr (Address_94 _ _) = "address"
    tagStr (Hr_94 _) = "hr"
    tagStr (Pre_94 _ _) = "pre"
    tagStr (Blockquote_94 _ _) = "blockquote"
    tagStr (Ins_94 _ _) = "ins"
    tagStr (Del_94 _ _) = "del"
    tagStr (A_94 _ _) = "a"
    tagStr (Span_94 _ _) = "span"
    tagStr (Bdo_94 _ _) = "bdo"
    tagStr (Br_94 _) = "br"
    tagStr (Em_94 _ _) = "em"
    tagStr (Strong_94 _ _) = "strong"
    tagStr (Dfn_94 _ _) = "dfn"
    tagStr (Code_94 _ _) = "code"
    tagStr (Samp_94 _ _) = "samp"
    tagStr (Kbd_94 _ _) = "kbd"
    tagStr (Var_94 _ _) = "var"
    tagStr (Cite_94 _ _) = "cite"
    tagStr (Abbr_94 _ _) = "abbr"
    tagStr (Acronym_94 _ _) = "acronym"
    tagStr (Q_94 _ _) = "q"
    tagStr (Sub_94 _ _) = "sub"
    tagStr (Sup_94 _ _) = "sup"
    tagStr (Tt_94 _ _) = "tt"
    tagStr (I_94 _ _) = "i"
    tagStr (B_94 _ _) = "b"
    tagStr (Big_94 _ _) = "big"
    tagStr (Small_94 _ _) = "small"
    tagStr (Object_94 _ _) = "object"
    tagStr (Img_94 _) = "img"
    tagStr (Map_94 _ _) = "map"
    tagStr (Form_94 _ _) = "form"
    tagStr (Label_94 _ _) = "label"
    tagStr (Input_94 _) = "input"
    tagStr (Select_94 _ _) = "select"
    tagStr (Textarea_94 _ _) = "textarea"
    tagStr (Fieldset_94 _ _) = "fieldset"
    tagStr (Button_94 _ _) = "button"
    tagStr (Table_94 _ _) = "table"
    tagStr (PCDATA_94 _ _) = "pcdata"
instance TagStr Ent95 where
    tagStr (Li_95 _ _) = "li"
instance TagStr Ent96 where
    tagStr (Dt_96 _ _) = "dt"
    tagStr (Dd_96 _ _) = "dd"
instance TagStr Ent97 where
    tagStr (Script_97 _ _) = "script"
    tagStr (Ins_97 _ _) = "ins"
    tagStr (Del_97 _ _) = "del"
    tagStr (A_97 _ _) = "a"
    tagStr (Span_97 _ _) = "span"
    tagStr (Bdo_97 _ _) = "bdo"
    tagStr (Br_97 _) = "br"
    tagStr (Em_97 _ _) = "em"
    tagStr (Strong_97 _ _) = "strong"
    tagStr (Dfn_97 _ _) = "dfn"
    tagStr (Code_97 _ _) = "code"
    tagStr (Samp_97 _ _) = "samp"
    tagStr (Kbd_97 _ _) = "kbd"
    tagStr (Var_97 _ _) = "var"
    tagStr (Cite_97 _ _) = "cite"
    tagStr (Abbr_97 _ _) = "abbr"
    tagStr (Acronym_97 _ _) = "acronym"
    tagStr (Q_97 _ _) = "q"
    tagStr (Sub_97 _ _) = "sub"
    tagStr (Sup_97 _ _) = "sup"
    tagStr (Tt_97 _ _) = "tt"
    tagStr (I_97 _ _) = "i"
    tagStr (B_97 _ _) = "b"
    tagStr (Big_97 _ _) = "big"
    tagStr (Small_97 _ _) = "small"
    tagStr (Map_97 _ _) = "map"
    tagStr (Label_97 _ _) = "label"
    tagStr (Input_97 _) = "input"
    tagStr (Select_97 _ _) = "select"
    tagStr (Textarea_97 _ _) = "textarea"
    tagStr (Button_97 _ _) = "button"
    tagStr (PCDATA_97 _ _) = "pcdata"
instance TagStr Ent98 where
    tagStr (Script_98 _ _) = "script"
    tagStr (Noscript_98 _ _) = "noscript"
    tagStr (Div_98 _ _) = "div"
    tagStr (P_98 _ _) = "p"
    tagStr (H1_98 _ _) = "h1"
    tagStr (H2_98 _ _) = "h2"
    tagStr (H3_98 _ _) = "h3"
    tagStr (H4_98 _ _) = "h4"
    tagStr (H5_98 _ _) = "h5"
    tagStr (H6_98 _ _) = "h6"
    tagStr (Ul_98 _ _) = "ul"
    tagStr (Ol_98 _ _) = "ol"
    tagStr (Dl_98 _ _) = "dl"
    tagStr (Address_98 _ _) = "address"
    tagStr (Hr_98 _) = "hr"
    tagStr (Pre_98 _ _) = "pre"
    tagStr (Blockquote_98 _ _) = "blockquote"
    tagStr (Ins_98 _ _) = "ins"
    tagStr (Del_98 _ _) = "del"
    tagStr (Fieldset_98 _ _) = "fieldset"
    tagStr (Table_98 _ _) = "table"
instance TagStr Ent99 where
    tagStr (PCDATA_99 _ _) = "pcdata"
instance TagStr Ent100 where
    tagStr (Script_100 _ _) = "script"
    tagStr (Noscript_100 _ _) = "noscript"
    tagStr (Div_100 _ _) = "div"
    tagStr (P_100 _ _) = "p"
    tagStr (H1_100 _ _) = "h1"
    tagStr (H2_100 _ _) = "h2"
    tagStr (H3_100 _ _) = "h3"
    tagStr (H4_100 _ _) = "h4"
    tagStr (H5_100 _ _) = "h5"
    tagStr (H6_100 _ _) = "h6"
    tagStr (Ul_100 _ _) = "ul"
    tagStr (Ol_100 _ _) = "ol"
    tagStr (Dl_100 _ _) = "dl"
    tagStr (Address_100 _ _) = "address"
    tagStr (Hr_100 _) = "hr"
    tagStr (Pre_100 _ _) = "pre"
    tagStr (Blockquote_100 _ _) = "blockquote"
    tagStr (Ins_100 _ _) = "ins"
    tagStr (Del_100 _ _) = "del"
    tagStr (A_100 _ _) = "a"
    tagStr (Span_100 _ _) = "span"
    tagStr (Bdo_100 _ _) = "bdo"
    tagStr (Br_100 _) = "br"
    tagStr (Em_100 _ _) = "em"
    tagStr (Strong_100 _ _) = "strong"
    tagStr (Dfn_100 _ _) = "dfn"
    tagStr (Code_100 _ _) = "code"
    tagStr (Samp_100 _ _) = "samp"
    tagStr (Kbd_100 _ _) = "kbd"
    tagStr (Var_100 _ _) = "var"
    tagStr (Cite_100 _ _) = "cite"
    tagStr (Abbr_100 _ _) = "abbr"
    tagStr (Acronym_100 _ _) = "acronym"
    tagStr (Q_100 _ _) = "q"
    tagStr (Sub_100 _ _) = "sub"
    tagStr (Sup_100 _ _) = "sup"
    tagStr (Tt_100 _ _) = "tt"
    tagStr (I_100 _ _) = "i"
    tagStr (B_100 _ _) = "b"
    tagStr (Big_100 _ _) = "big"
    tagStr (Small_100 _ _) = "small"
    tagStr (Object_100 _ _) = "object"
    tagStr (Img_100 _) = "img"
    tagStr (Map_100 _ _) = "map"
    tagStr (Label_100 _ _) = "label"
    tagStr (Input_100 _) = "input"
    tagStr (Select_100 _ _) = "select"
    tagStr (Textarea_100 _ _) = "textarea"
    tagStr (Fieldset_100 _ _) = "fieldset"
    tagStr (Button_100 _ _) = "button"
    tagStr (Table_100 _ _) = "table"
    tagStr (PCDATA_100 _ _) = "pcdata"
instance TagStr Ent101 where
    tagStr (PCDATA_101 _ _) = "pcdata"
instance TagStr Ent102 where
    tagStr (Script_102 _ _) = "script"
    tagStr (Noscript_102 _ _) = "noscript"
    tagStr (Div_102 _ _) = "div"
    tagStr (P_102 _ _) = "p"
    tagStr (H1_102 _ _) = "h1"
    tagStr (H2_102 _ _) = "h2"
    tagStr (H3_102 _ _) = "h3"
    tagStr (H4_102 _ _) = "h4"
    tagStr (H5_102 _ _) = "h5"
    tagStr (H6_102 _ _) = "h6"
    tagStr (Ul_102 _ _) = "ul"
    tagStr (Ol_102 _ _) = "ol"
    tagStr (Dl_102 _ _) = "dl"
    tagStr (Address_102 _ _) = "address"
    tagStr (Hr_102 _) = "hr"
    tagStr (Pre_102 _ _) = "pre"
    tagStr (Blockquote_102 _ _) = "blockquote"
    tagStr (Ins_102 _ _) = "ins"
    tagStr (Del_102 _ _) = "del"
    tagStr (Span_102 _ _) = "span"
    tagStr (Bdo_102 _ _) = "bdo"
    tagStr (Br_102 _) = "br"
    tagStr (Em_102 _ _) = "em"
    tagStr (Strong_102 _ _) = "strong"
    tagStr (Dfn_102 _ _) = "dfn"
    tagStr (Code_102 _ _) = "code"
    tagStr (Samp_102 _ _) = "samp"
    tagStr (Kbd_102 _ _) = "kbd"
    tagStr (Var_102 _ _) = "var"
    tagStr (Cite_102 _ _) = "cite"
    tagStr (Abbr_102 _ _) = "abbr"
    tagStr (Acronym_102 _ _) = "acronym"
    tagStr (Q_102 _ _) = "q"
    tagStr (Sub_102 _ _) = "sub"
    tagStr (Sup_102 _ _) = "sup"
    tagStr (Tt_102 _ _) = "tt"
    tagStr (I_102 _ _) = "i"
    tagStr (B_102 _ _) = "b"
    tagStr (Big_102 _ _) = "big"
    tagStr (Small_102 _ _) = "small"
    tagStr (Object_102 _ _) = "object"
    tagStr (Param_102 _) = "param"
    tagStr (Img_102 _) = "img"
    tagStr (Map_102 _ _) = "map"
    tagStr (Label_102 _ _) = "label"
    tagStr (Input_102 _) = "input"
    tagStr (Select_102 _ _) = "select"
    tagStr (Textarea_102 _ _) = "textarea"
    tagStr (Fieldset_102 _ _) = "fieldset"
    tagStr (Button_102 _ _) = "button"
    tagStr (Table_102 _ _) = "table"
    tagStr (PCDATA_102 _ _) = "pcdata"
instance TagStr Ent103 where
    tagStr (Script_103 _ _) = "script"
    tagStr (Noscript_103 _ _) = "noscript"
    tagStr (Div_103 _ _) = "div"
    tagStr (P_103 _ _) = "p"
    tagStr (H1_103 _ _) = "h1"
    tagStr (H2_103 _ _) = "h2"
    tagStr (H3_103 _ _) = "h3"
    tagStr (H4_103 _ _) = "h4"
    tagStr (H5_103 _ _) = "h5"
    tagStr (H6_103 _ _) = "h6"
    tagStr (Ul_103 _ _) = "ul"
    tagStr (Ol_103 _ _) = "ol"
    tagStr (Dl_103 _ _) = "dl"
    tagStr (Address_103 _ _) = "address"
    tagStr (Hr_103 _) = "hr"
    tagStr (Pre_103 _ _) = "pre"
    tagStr (Blockquote_103 _ _) = "blockquote"
    tagStr (Ins_103 _ _) = "ins"
    tagStr (Del_103 _ _) = "del"
    tagStr (Area_103 _) = "area"
    tagStr (Fieldset_103 _ _) = "fieldset"
    tagStr (Table_103 _ _) = "table"
instance TagStr Ent104 where
    tagStr (PCDATA_104 _ _) = "pcdata"
instance TagStr Ent105 where
    tagStr (Script_105 _ _) = "script"
    tagStr (Noscript_105 _ _) = "noscript"
    tagStr (Div_105 _ _) = "div"
    tagStr (P_105 _ _) = "p"
    tagStr (H1_105 _ _) = "h1"
    tagStr (H2_105 _ _) = "h2"
    tagStr (H3_105 _ _) = "h3"
    tagStr (H4_105 _ _) = "h4"
    tagStr (H5_105 _ _) = "h5"
    tagStr (H6_105 _ _) = "h6"
    tagStr (Ul_105 _ _) = "ul"
    tagStr (Ol_105 _ _) = "ol"
    tagStr (Dl_105 _ _) = "dl"
    tagStr (Address_105 _ _) = "address"
    tagStr (Hr_105 _) = "hr"
    tagStr (Pre_105 _ _) = "pre"
    tagStr (Blockquote_105 _ _) = "blockquote"
    tagStr (Ins_105 _ _) = "ins"
    tagStr (Del_105 _ _) = "del"
    tagStr (Span_105 _ _) = "span"
    tagStr (Bdo_105 _ _) = "bdo"
    tagStr (Br_105 _) = "br"
    tagStr (Em_105 _ _) = "em"
    tagStr (Strong_105 _ _) = "strong"
    tagStr (Dfn_105 _ _) = "dfn"
    tagStr (Code_105 _ _) = "code"
    tagStr (Samp_105 _ _) = "samp"
    tagStr (Kbd_105 _ _) = "kbd"
    tagStr (Var_105 _ _) = "var"
    tagStr (Cite_105 _ _) = "cite"
    tagStr (Abbr_105 _ _) = "abbr"
    tagStr (Acronym_105 _ _) = "acronym"
    tagStr (Q_105 _ _) = "q"
    tagStr (Sub_105 _ _) = "sub"
    tagStr (Sup_105 _ _) = "sup"
    tagStr (Tt_105 _ _) = "tt"
    tagStr (I_105 _ _) = "i"
    tagStr (B_105 _ _) = "b"
    tagStr (Big_105 _ _) = "big"
    tagStr (Small_105 _ _) = "small"
    tagStr (Object_105 _ _) = "object"
    tagStr (Param_105 _) = "param"
    tagStr (Img_105 _) = "img"
    tagStr (Map_105 _ _) = "map"
    tagStr (Input_105 _) = "input"
    tagStr (Select_105 _ _) = "select"
    tagStr (Textarea_105 _ _) = "textarea"
    tagStr (Fieldset_105 _ _) = "fieldset"
    tagStr (Button_105 _ _) = "button"
    tagStr (Table_105 _ _) = "table"
    tagStr (PCDATA_105 _ _) = "pcdata"
instance TagStr Ent106 where
    tagStr (Script_106 _ _) = "script"
    tagStr (Noscript_106 _ _) = "noscript"
    tagStr (Div_106 _ _) = "div"
    tagStr (P_106 _ _) = "p"
    tagStr (H1_106 _ _) = "h1"
    tagStr (H2_106 _ _) = "h2"
    tagStr (H3_106 _ _) = "h3"
    tagStr (H4_106 _ _) = "h4"
    tagStr (H5_106 _ _) = "h5"
    tagStr (H6_106 _ _) = "h6"
    tagStr (Ul_106 _ _) = "ul"
    tagStr (Ol_106 _ _) = "ol"
    tagStr (Dl_106 _ _) = "dl"
    tagStr (Address_106 _ _) = "address"
    tagStr (Hr_106 _) = "hr"
    tagStr (Pre_106 _ _) = "pre"
    tagStr (Blockquote_106 _ _) = "blockquote"
    tagStr (Ins_106 _ _) = "ins"
    tagStr (Del_106 _ _) = "del"
    tagStr (Area_106 _) = "area"
    tagStr (Fieldset_106 _ _) = "fieldset"
    tagStr (Table_106 _ _) = "table"
instance TagStr Ent107 where
    tagStr (Optgroup_107 _ _) = "optgroup"
    tagStr (Option_107 _ _) = "option"
instance TagStr Ent108 where
    tagStr (Option_108 _ _) = "option"
instance TagStr Ent109 where
    tagStr (Script_109 _ _) = "script"
    tagStr (Noscript_109 _ _) = "noscript"
    tagStr (Div_109 _ _) = "div"
    tagStr (P_109 _ _) = "p"
    tagStr (H1_109 _ _) = "h1"
    tagStr (H2_109 _ _) = "h2"
    tagStr (H3_109 _ _) = "h3"
    tagStr (H4_109 _ _) = "h4"
    tagStr (H5_109 _ _) = "h5"
    tagStr (H6_109 _ _) = "h6"
    tagStr (Ul_109 _ _) = "ul"
    tagStr (Ol_109 _ _) = "ol"
    tagStr (Dl_109 _ _) = "dl"
    tagStr (Address_109 _ _) = "address"
    tagStr (Hr_109 _) = "hr"
    tagStr (Pre_109 _ _) = "pre"
    tagStr (Blockquote_109 _ _) = "blockquote"
    tagStr (Ins_109 _ _) = "ins"
    tagStr (Del_109 _ _) = "del"
    tagStr (Span_109 _ _) = "span"
    tagStr (Bdo_109 _ _) = "bdo"
    tagStr (Br_109 _) = "br"
    tagStr (Em_109 _ _) = "em"
    tagStr (Strong_109 _ _) = "strong"
    tagStr (Dfn_109 _ _) = "dfn"
    tagStr (Code_109 _ _) = "code"
    tagStr (Samp_109 _ _) = "samp"
    tagStr (Kbd_109 _ _) = "kbd"
    tagStr (Var_109 _ _) = "var"
    tagStr (Cite_109 _ _) = "cite"
    tagStr (Abbr_109 _ _) = "abbr"
    tagStr (Acronym_109 _ _) = "acronym"
    tagStr (Q_109 _ _) = "q"
    tagStr (Sub_109 _ _) = "sub"
    tagStr (Sup_109 _ _) = "sup"
    tagStr (Tt_109 _ _) = "tt"
    tagStr (I_109 _ _) = "i"
    tagStr (B_109 _ _) = "b"
    tagStr (Big_109 _ _) = "big"
    tagStr (Small_109 _ _) = "small"
    tagStr (Object_109 _ _) = "object"
    tagStr (Img_109 _) = "img"
    tagStr (Map_109 _ _) = "map"
    tagStr (Table_109 _ _) = "table"
    tagStr (PCDATA_109 _ _) = "pcdata"
instance TagStr Ent110 where
    tagStr (Optgroup_110 _ _) = "optgroup"
    tagStr (Option_110 _ _) = "option"
instance TagStr Ent111 where
    tagStr (Option_111 _ _) = "option"
instance TagStr Ent112 where
    tagStr (Script_112 _ _) = "script"
    tagStr (Noscript_112 _ _) = "noscript"
    tagStr (Div_112 _ _) = "div"
    tagStr (P_112 _ _) = "p"
    tagStr (H1_112 _ _) = "h1"
    tagStr (H2_112 _ _) = "h2"
    tagStr (H3_112 _ _) = "h3"
    tagStr (H4_112 _ _) = "h4"
    tagStr (H5_112 _ _) = "h5"
    tagStr (H6_112 _ _) = "h6"
    tagStr (Ul_112 _ _) = "ul"
    tagStr (Ol_112 _ _) = "ol"
    tagStr (Dl_112 _ _) = "dl"
    tagStr (Address_112 _ _) = "address"
    tagStr (Hr_112 _) = "hr"
    tagStr (Pre_112 _ _) = "pre"
    tagStr (Blockquote_112 _ _) = "blockquote"
    tagStr (Ins_112 _ _) = "ins"
    tagStr (Del_112 _ _) = "del"
    tagStr (Span_112 _ _) = "span"
    tagStr (Bdo_112 _ _) = "bdo"
    tagStr (Br_112 _) = "br"
    tagStr (Em_112 _ _) = "em"
    tagStr (Strong_112 _ _) = "strong"
    tagStr (Dfn_112 _ _) = "dfn"
    tagStr (Code_112 _ _) = "code"
    tagStr (Samp_112 _ _) = "samp"
    tagStr (Kbd_112 _ _) = "kbd"
    tagStr (Var_112 _ _) = "var"
    tagStr (Cite_112 _ _) = "cite"
    tagStr (Abbr_112 _ _) = "abbr"
    tagStr (Acronym_112 _ _) = "acronym"
    tagStr (Q_112 _ _) = "q"
    tagStr (Sub_112 _ _) = "sub"
    tagStr (Sup_112 _ _) = "sup"
    tagStr (Tt_112 _ _) = "tt"
    tagStr (I_112 _ _) = "i"
    tagStr (B_112 _ _) = "b"
    tagStr (Big_112 _ _) = "big"
    tagStr (Small_112 _ _) = "small"
    tagStr (Object_112 _ _) = "object"
    tagStr (Img_112 _) = "img"
    tagStr (Map_112 _ _) = "map"
    tagStr (Table_112 _ _) = "table"
    tagStr (PCDATA_112 _ _) = "pcdata"
instance TagStr Ent113 where
    tagStr (Script_113 _ _) = "script"
    tagStr (Ins_113 _ _) = "ins"
    tagStr (Del_113 _ _) = "del"
    tagStr (A_113 _ _) = "a"
    tagStr (Span_113 _ _) = "span"
    tagStr (Bdo_113 _ _) = "bdo"
    tagStr (Br_113 _) = "br"
    tagStr (Em_113 _ _) = "em"
    tagStr (Strong_113 _ _) = "strong"
    tagStr (Dfn_113 _ _) = "dfn"
    tagStr (Code_113 _ _) = "code"
    tagStr (Samp_113 _ _) = "samp"
    tagStr (Kbd_113 _ _) = "kbd"
    tagStr (Var_113 _ _) = "var"
    tagStr (Cite_113 _ _) = "cite"
    tagStr (Abbr_113 _ _) = "abbr"
    tagStr (Acronym_113 _ _) = "acronym"
    tagStr (Q_113 _ _) = "q"
    tagStr (Sub_113 _ _) = "sub"
    tagStr (Sup_113 _ _) = "sup"
    tagStr (Tt_113 _ _) = "tt"
    tagStr (I_113 _ _) = "i"
    tagStr (B_113 _ _) = "b"
    tagStr (Big_113 _ _) = "big"
    tagStr (Small_113 _ _) = "small"
    tagStr (Object_113 _ _) = "object"
    tagStr (Img_113 _) = "img"
    tagStr (Map_113 _ _) = "map"
    tagStr (Label_113 _ _) = "label"
    tagStr (Input_113 _) = "input"
    tagStr (Select_113 _ _) = "select"
    tagStr (Textarea_113 _ _) = "textarea"
    tagStr (Button_113 _ _) = "button"
    tagStr (PCDATA_113 _ _) = "pcdata"
instance TagStr Ent114 where
    tagStr (Script_114 _ _) = "script"
    tagStr (Noscript_114 _ _) = "noscript"
    tagStr (Div_114 _ _) = "div"
    tagStr (P_114 _ _) = "p"
    tagStr (H1_114 _ _) = "h1"
    tagStr (H2_114 _ _) = "h2"
    tagStr (H3_114 _ _) = "h3"
    tagStr (H4_114 _ _) = "h4"
    tagStr (H5_114 _ _) = "h5"
    tagStr (H6_114 _ _) = "h6"
    tagStr (Ul_114 _ _) = "ul"
    tagStr (Ol_114 _ _) = "ol"
    tagStr (Dl_114 _ _) = "dl"
    tagStr (Address_114 _ _) = "address"
    tagStr (Hr_114 _) = "hr"
    tagStr (Pre_114 _ _) = "pre"
    tagStr (Blockquote_114 _ _) = "blockquote"
    tagStr (Ins_114 _ _) = "ins"
    tagStr (Del_114 _ _) = "del"
    tagStr (A_114 _ _) = "a"
    tagStr (Span_114 _ _) = "span"
    tagStr (Bdo_114 _ _) = "bdo"
    tagStr (Br_114 _) = "br"
    tagStr (Em_114 _ _) = "em"
    tagStr (Strong_114 _ _) = "strong"
    tagStr (Dfn_114 _ _) = "dfn"
    tagStr (Code_114 _ _) = "code"
    tagStr (Samp_114 _ _) = "samp"
    tagStr (Kbd_114 _ _) = "kbd"
    tagStr (Var_114 _ _) = "var"
    tagStr (Cite_114 _ _) = "cite"
    tagStr (Abbr_114 _ _) = "abbr"
    tagStr (Acronym_114 _ _) = "acronym"
    tagStr (Q_114 _ _) = "q"
    tagStr (Sub_114 _ _) = "sub"
    tagStr (Sup_114 _ _) = "sup"
    tagStr (Tt_114 _ _) = "tt"
    tagStr (I_114 _ _) = "i"
    tagStr (B_114 _ _) = "b"
    tagStr (Big_114 _ _) = "big"
    tagStr (Small_114 _ _) = "small"
    tagStr (Object_114 _ _) = "object"
    tagStr (Param_114 _) = "param"
    tagStr (Img_114 _) = "img"
    tagStr (Map_114 _ _) = "map"
    tagStr (Label_114 _ _) = "label"
    tagStr (Input_114 _) = "input"
    tagStr (Select_114 _ _) = "select"
    tagStr (Textarea_114 _ _) = "textarea"
    tagStr (Fieldset_114 _ _) = "fieldset"
    tagStr (Button_114 _ _) = "button"
    tagStr (Table_114 _ _) = "table"
    tagStr (PCDATA_114 _ _) = "pcdata"
instance TagStr Ent115 where
    tagStr (Script_115 _ _) = "script"
    tagStr (Noscript_115 _ _) = "noscript"
    tagStr (Div_115 _ _) = "div"
    tagStr (P_115 _ _) = "p"
    tagStr (H1_115 _ _) = "h1"
    tagStr (H2_115 _ _) = "h2"
    tagStr (H3_115 _ _) = "h3"
    tagStr (H4_115 _ _) = "h4"
    tagStr (H5_115 _ _) = "h5"
    tagStr (H6_115 _ _) = "h6"
    tagStr (Ul_115 _ _) = "ul"
    tagStr (Ol_115 _ _) = "ol"
    tagStr (Dl_115 _ _) = "dl"
    tagStr (Address_115 _ _) = "address"
    tagStr (Hr_115 _) = "hr"
    tagStr (Pre_115 _ _) = "pre"
    tagStr (Blockquote_115 _ _) = "blockquote"
    tagStr (Ins_115 _ _) = "ins"
    tagStr (Del_115 _ _) = "del"
    tagStr (Area_115 _) = "area"
    tagStr (Fieldset_115 _ _) = "fieldset"
    tagStr (Table_115 _ _) = "table"
instance TagStr Ent116 where
    tagStr (PCDATA_116 _ _) = "pcdata"
instance TagStr Ent117 where
    tagStr (Script_117 _ _) = "script"
    tagStr (Noscript_117 _ _) = "noscript"
    tagStr (Div_117 _ _) = "div"
    tagStr (P_117 _ _) = "p"
    tagStr (H1_117 _ _) = "h1"
    tagStr (H2_117 _ _) = "h2"
    tagStr (H3_117 _ _) = "h3"
    tagStr (H4_117 _ _) = "h4"
    tagStr (H5_117 _ _) = "h5"
    tagStr (H6_117 _ _) = "h6"
    tagStr (Ul_117 _ _) = "ul"
    tagStr (Ol_117 _ _) = "ol"
    tagStr (Dl_117 _ _) = "dl"
    tagStr (Address_117 _ _) = "address"
    tagStr (Hr_117 _) = "hr"
    tagStr (Pre_117 _ _) = "pre"
    tagStr (Blockquote_117 _ _) = "blockquote"
    tagStr (Ins_117 _ _) = "ins"
    tagStr (Del_117 _ _) = "del"
    tagStr (A_117 _ _) = "a"
    tagStr (Span_117 _ _) = "span"
    tagStr (Bdo_117 _ _) = "bdo"
    tagStr (Br_117 _) = "br"
    tagStr (Em_117 _ _) = "em"
    tagStr (Strong_117 _ _) = "strong"
    tagStr (Dfn_117 _ _) = "dfn"
    tagStr (Code_117 _ _) = "code"
    tagStr (Samp_117 _ _) = "samp"
    tagStr (Kbd_117 _ _) = "kbd"
    tagStr (Var_117 _ _) = "var"
    tagStr (Cite_117 _ _) = "cite"
    tagStr (Abbr_117 _ _) = "abbr"
    tagStr (Acronym_117 _ _) = "acronym"
    tagStr (Q_117 _ _) = "q"
    tagStr (Sub_117 _ _) = "sub"
    tagStr (Sup_117 _ _) = "sup"
    tagStr (Tt_117 _ _) = "tt"
    tagStr (I_117 _ _) = "i"
    tagStr (B_117 _ _) = "b"
    tagStr (Big_117 _ _) = "big"
    tagStr (Small_117 _ _) = "small"
    tagStr (Object_117 _ _) = "object"
    tagStr (Param_117 _) = "param"
    tagStr (Img_117 _) = "img"
    tagStr (Map_117 _ _) = "map"
    tagStr (Input_117 _) = "input"
    tagStr (Select_117 _ _) = "select"
    tagStr (Textarea_117 _ _) = "textarea"
    tagStr (Fieldset_117 _ _) = "fieldset"
    tagStr (Button_117 _ _) = "button"
    tagStr (Table_117 _ _) = "table"
    tagStr (PCDATA_117 _ _) = "pcdata"
instance TagStr Ent118 where
    tagStr (Script_118 _ _) = "script"
    tagStr (Noscript_118 _ _) = "noscript"
    tagStr (Div_118 _ _) = "div"
    tagStr (P_118 _ _) = "p"
    tagStr (H1_118 _ _) = "h1"
    tagStr (H2_118 _ _) = "h2"
    tagStr (H3_118 _ _) = "h3"
    tagStr (H4_118 _ _) = "h4"
    tagStr (H5_118 _ _) = "h5"
    tagStr (H6_118 _ _) = "h6"
    tagStr (Ul_118 _ _) = "ul"
    tagStr (Ol_118 _ _) = "ol"
    tagStr (Dl_118 _ _) = "dl"
    tagStr (Address_118 _ _) = "address"
    tagStr (Hr_118 _) = "hr"
    tagStr (Pre_118 _ _) = "pre"
    tagStr (Blockquote_118 _ _) = "blockquote"
    tagStr (Ins_118 _ _) = "ins"
    tagStr (Del_118 _ _) = "del"
    tagStr (Area_118 _) = "area"
    tagStr (Fieldset_118 _ _) = "fieldset"
    tagStr (Table_118 _ _) = "table"
instance TagStr Ent119 where
    tagStr (Optgroup_119 _ _) = "optgroup"
    tagStr (Option_119 _ _) = "option"
instance TagStr Ent120 where
    tagStr (Option_120 _ _) = "option"
instance TagStr Ent121 where
    tagStr (Script_121 _ _) = "script"
    tagStr (Noscript_121 _ _) = "noscript"
    tagStr (Div_121 _ _) = "div"
    tagStr (P_121 _ _) = "p"
    tagStr (H1_121 _ _) = "h1"
    tagStr (H2_121 _ _) = "h2"
    tagStr (H3_121 _ _) = "h3"
    tagStr (H4_121 _ _) = "h4"
    tagStr (H5_121 _ _) = "h5"
    tagStr (H6_121 _ _) = "h6"
    tagStr (Ul_121 _ _) = "ul"
    tagStr (Ol_121 _ _) = "ol"
    tagStr (Dl_121 _ _) = "dl"
    tagStr (Address_121 _ _) = "address"
    tagStr (Hr_121 _) = "hr"
    tagStr (Pre_121 _ _) = "pre"
    tagStr (Blockquote_121 _ _) = "blockquote"
    tagStr (Ins_121 _ _) = "ins"
    tagStr (Del_121 _ _) = "del"
    tagStr (Span_121 _ _) = "span"
    tagStr (Bdo_121 _ _) = "bdo"
    tagStr (Br_121 _) = "br"
    tagStr (Em_121 _ _) = "em"
    tagStr (Strong_121 _ _) = "strong"
    tagStr (Dfn_121 _ _) = "dfn"
    tagStr (Code_121 _ _) = "code"
    tagStr (Samp_121 _ _) = "samp"
    tagStr (Kbd_121 _ _) = "kbd"
    tagStr (Var_121 _ _) = "var"
    tagStr (Cite_121 _ _) = "cite"
    tagStr (Abbr_121 _ _) = "abbr"
    tagStr (Acronym_121 _ _) = "acronym"
    tagStr (Q_121 _ _) = "q"
    tagStr (Sub_121 _ _) = "sub"
    tagStr (Sup_121 _ _) = "sup"
    tagStr (Tt_121 _ _) = "tt"
    tagStr (I_121 _ _) = "i"
    tagStr (B_121 _ _) = "b"
    tagStr (Big_121 _ _) = "big"
    tagStr (Small_121 _ _) = "small"
    tagStr (Object_121 _ _) = "object"
    tagStr (Img_121 _) = "img"
    tagStr (Map_121 _ _) = "map"
    tagStr (Table_121 _ _) = "table"
    tagStr (PCDATA_121 _ _) = "pcdata"
instance TagStr Ent122 where
    tagStr (Optgroup_122 _ _) = "optgroup"
    tagStr (Option_122 _ _) = "option"
instance TagStr Ent123 where
    tagStr (Option_123 _ _) = "option"
instance TagStr Ent124 where
    tagStr (Script_124 _ _) = "script"
    tagStr (Noscript_124 _ _) = "noscript"
    tagStr (Div_124 _ _) = "div"
    tagStr (P_124 _ _) = "p"
    tagStr (H1_124 _ _) = "h1"
    tagStr (H2_124 _ _) = "h2"
    tagStr (H3_124 _ _) = "h3"
    tagStr (H4_124 _ _) = "h4"
    tagStr (H5_124 _ _) = "h5"
    tagStr (H6_124 _ _) = "h6"
    tagStr (Ul_124 _ _) = "ul"
    tagStr (Ol_124 _ _) = "ol"
    tagStr (Dl_124 _ _) = "dl"
    tagStr (Address_124 _ _) = "address"
    tagStr (Hr_124 _) = "hr"
    tagStr (Pre_124 _ _) = "pre"
    tagStr (Blockquote_124 _ _) = "blockquote"
    tagStr (Ins_124 _ _) = "ins"
    tagStr (Del_124 _ _) = "del"
    tagStr (Span_124 _ _) = "span"
    tagStr (Bdo_124 _ _) = "bdo"
    tagStr (Br_124 _) = "br"
    tagStr (Em_124 _ _) = "em"
    tagStr (Strong_124 _ _) = "strong"
    tagStr (Dfn_124 _ _) = "dfn"
    tagStr (Code_124 _ _) = "code"
    tagStr (Samp_124 _ _) = "samp"
    tagStr (Kbd_124 _ _) = "kbd"
    tagStr (Var_124 _ _) = "var"
    tagStr (Cite_124 _ _) = "cite"
    tagStr (Abbr_124 _ _) = "abbr"
    tagStr (Acronym_124 _ _) = "acronym"
    tagStr (Q_124 _ _) = "q"
    tagStr (Sub_124 _ _) = "sub"
    tagStr (Sup_124 _ _) = "sup"
    tagStr (Tt_124 _ _) = "tt"
    tagStr (I_124 _ _) = "i"
    tagStr (B_124 _ _) = "b"
    tagStr (Big_124 _ _) = "big"
    tagStr (Small_124 _ _) = "small"
    tagStr (Object_124 _ _) = "object"
    tagStr (Img_124 _) = "img"
    tagStr (Map_124 _ _) = "map"
    tagStr (Table_124 _ _) = "table"
    tagStr (PCDATA_124 _ _) = "pcdata"
instance TagStr Ent125 where
    tagStr (Li_125 _ _) = "li"
instance TagStr Ent126 where
    tagStr (Dt_126 _ _) = "dt"
    tagStr (Dd_126 _ _) = "dd"
instance TagStr Ent127 where
    tagStr (Script_127 _ _) = "script"
    tagStr (Ins_127 _ _) = "ins"
    tagStr (Del_127 _ _) = "del"
    tagStr (A_127 _ _) = "a"
    tagStr (Span_127 _ _) = "span"
    tagStr (Bdo_127 _ _) = "bdo"
    tagStr (Br_127 _) = "br"
    tagStr (Em_127 _ _) = "em"
    tagStr (Strong_127 _ _) = "strong"
    tagStr (Dfn_127 _ _) = "dfn"
    tagStr (Code_127 _ _) = "code"
    tagStr (Samp_127 _ _) = "samp"
    tagStr (Kbd_127 _ _) = "kbd"
    tagStr (Var_127 _ _) = "var"
    tagStr (Cite_127 _ _) = "cite"
    tagStr (Abbr_127 _ _) = "abbr"
    tagStr (Acronym_127 _ _) = "acronym"
    tagStr (Q_127 _ _) = "q"
    tagStr (Sub_127 _ _) = "sub"
    tagStr (Sup_127 _ _) = "sup"
    tagStr (Tt_127 _ _) = "tt"
    tagStr (I_127 _ _) = "i"
    tagStr (B_127 _ _) = "b"
    tagStr (Big_127 _ _) = "big"
    tagStr (Small_127 _ _) = "small"
    tagStr (Map_127 _ _) = "map"
    tagStr (Label_127 _ _) = "label"
    tagStr (Input_127 _) = "input"
    tagStr (Select_127 _ _) = "select"
    tagStr (Textarea_127 _ _) = "textarea"
    tagStr (Button_127 _ _) = "button"
    tagStr (PCDATA_127 _ _) = "pcdata"
instance TagStr Ent128 where
    tagStr (Script_128 _ _) = "script"
    tagStr (Noscript_128 _ _) = "noscript"
    tagStr (Div_128 _ _) = "div"
    tagStr (P_128 _ _) = "p"
    tagStr (H1_128 _ _) = "h1"
    tagStr (H2_128 _ _) = "h2"
    tagStr (H3_128 _ _) = "h3"
    tagStr (H4_128 _ _) = "h4"
    tagStr (H5_128 _ _) = "h5"
    tagStr (H6_128 _ _) = "h6"
    tagStr (Ul_128 _ _) = "ul"
    tagStr (Ol_128 _ _) = "ol"
    tagStr (Dl_128 _ _) = "dl"
    tagStr (Address_128 _ _) = "address"
    tagStr (Hr_128 _) = "hr"
    tagStr (Pre_128 _ _) = "pre"
    tagStr (Blockquote_128 _ _) = "blockquote"
    tagStr (Ins_128 _ _) = "ins"
    tagStr (Del_128 _ _) = "del"
    tagStr (A_128 _ _) = "a"
    tagStr (Span_128 _ _) = "span"
    tagStr (Bdo_128 _ _) = "bdo"
    tagStr (Br_128 _) = "br"
    tagStr (Em_128 _ _) = "em"
    tagStr (Strong_128 _ _) = "strong"
    tagStr (Dfn_128 _ _) = "dfn"
    tagStr (Code_128 _ _) = "code"
    tagStr (Samp_128 _ _) = "samp"
    tagStr (Kbd_128 _ _) = "kbd"
    tagStr (Var_128 _ _) = "var"
    tagStr (Cite_128 _ _) = "cite"
    tagStr (Abbr_128 _ _) = "abbr"
    tagStr (Acronym_128 _ _) = "acronym"
    tagStr (Q_128 _ _) = "q"
    tagStr (Sub_128 _ _) = "sub"
    tagStr (Sup_128 _ _) = "sup"
    tagStr (Tt_128 _ _) = "tt"
    tagStr (I_128 _ _) = "i"
    tagStr (B_128 _ _) = "b"
    tagStr (Big_128 _ _) = "big"
    tagStr (Small_128 _ _) = "small"
    tagStr (Object_128 _ _) = "object"
    tagStr (Img_128 _) = "img"
    tagStr (Map_128 _ _) = "map"
    tagStr (Label_128 _ _) = "label"
    tagStr (Input_128 _) = "input"
    tagStr (Select_128 _ _) = "select"
    tagStr (Textarea_128 _ _) = "textarea"
    tagStr (Fieldset_128 _ _) = "fieldset"
    tagStr (Legend_128 _ _) = "legend"
    tagStr (Button_128 _ _) = "button"
    tagStr (Table_128 _ _) = "table"
    tagStr (PCDATA_128 _ _) = "pcdata"
instance TagStr Ent129 where
    tagStr (Caption_129 _ _) = "caption"
    tagStr (Thead_129 _ _) = "thead"
    tagStr (Tfoot_129 _ _) = "tfoot"
    tagStr (Tbody_129 _ _) = "tbody"
    tagStr (Colgroup_129 _ _) = "colgroup"
    tagStr (Col_129 _) = "col"
    tagStr (Tr_129 _ _) = "tr"
instance TagStr Ent130 where
    tagStr (Tr_130 _ _) = "tr"
instance TagStr Ent131 where
    tagStr (Col_131 _) = "col"
instance TagStr Ent132 where
    tagStr (Th_132 _ _) = "th"
    tagStr (Td_132 _ _) = "td"
instance TagStr Ent133 where
    tagStr (Script_133 _ _) = "script"
    tagStr (Noscript_133 _ _) = "noscript"
    tagStr (Div_133 _ _) = "div"
    tagStr (P_133 _ _) = "p"
    tagStr (H1_133 _ _) = "h1"
    tagStr (H2_133 _ _) = "h2"
    tagStr (H3_133 _ _) = "h3"
    tagStr (H4_133 _ _) = "h4"
    tagStr (H5_133 _ _) = "h5"
    tagStr (H6_133 _ _) = "h6"
    tagStr (Ul_133 _ _) = "ul"
    tagStr (Ol_133 _ _) = "ol"
    tagStr (Dl_133 _ _) = "dl"
    tagStr (Address_133 _ _) = "address"
    tagStr (Hr_133 _) = "hr"
    tagStr (Pre_133 _ _) = "pre"
    tagStr (Blockquote_133 _ _) = "blockquote"
    tagStr (Ins_133 _ _) = "ins"
    tagStr (Del_133 _ _) = "del"
    tagStr (A_133 _ _) = "a"
    tagStr (Span_133 _ _) = "span"
    tagStr (Bdo_133 _ _) = "bdo"
    tagStr (Br_133 _) = "br"
    tagStr (Em_133 _ _) = "em"
    tagStr (Strong_133 _ _) = "strong"
    tagStr (Dfn_133 _ _) = "dfn"
    tagStr (Code_133 _ _) = "code"
    tagStr (Samp_133 _ _) = "samp"
    tagStr (Kbd_133 _ _) = "kbd"
    tagStr (Var_133 _ _) = "var"
    tagStr (Cite_133 _ _) = "cite"
    tagStr (Abbr_133 _ _) = "abbr"
    tagStr (Acronym_133 _ _) = "acronym"
    tagStr (Q_133 _ _) = "q"
    tagStr (Sub_133 _ _) = "sub"
    tagStr (Sup_133 _ _) = "sup"
    tagStr (Tt_133 _ _) = "tt"
    tagStr (I_133 _ _) = "i"
    tagStr (B_133 _ _) = "b"
    tagStr (Big_133 _ _) = "big"
    tagStr (Small_133 _ _) = "small"
    tagStr (Object_133 _ _) = "object"
    tagStr (Img_133 _) = "img"
    tagStr (Map_133 _ _) = "map"
    tagStr (Form_133 _ _) = "form"
    tagStr (Label_133 _ _) = "label"
    tagStr (Input_133 _) = "input"
    tagStr (Select_133 _ _) = "select"
    tagStr (Textarea_133 _ _) = "textarea"
    tagStr (Fieldset_133 _ _) = "fieldset"
    tagStr (Legend_133 _ _) = "legend"
    tagStr (Button_133 _ _) = "button"
    tagStr (Table_133 _ _) = "table"
    tagStr (PCDATA_133 _ _) = "pcdata"
instance TagStr Ent134 where
    tagStr (Caption_134 _ _) = "caption"
    tagStr (Thead_134 _ _) = "thead"
    tagStr (Tfoot_134 _ _) = "tfoot"
    tagStr (Tbody_134 _ _) = "tbody"
    tagStr (Colgroup_134 _ _) = "colgroup"
    tagStr (Col_134 _) = "col"
    tagStr (Tr_134 _ _) = "tr"
instance TagStr Ent135 where
    tagStr (Tr_135 _ _) = "tr"
instance TagStr Ent136 where
    tagStr (Col_136 _) = "col"
instance TagStr Ent137 where
    tagStr (Th_137 _ _) = "th"
    tagStr (Td_137 _ _) = "td"

class TagChildren a where
    tagChildren :: a -> [(Int,String,[String],[U.ByteString],[U.ByteString])]
instance TagChildren Ent where
    tagChildren (Html att c) = (0,"html",map tagStr c,[],[]):(concatMap tagChildren c)
instance TagChildren Ent0 where
    tagChildren (Head_0 a c) = (1,"head",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Body_0 a c) = (9,"body",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent1 where
    tagChildren (Title_1 a c) = (2,"title",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Base_1 a) = [(-1,"base",[],(map fst (map renderAtt a)),[href_byte])]
    tagChildren (Meta_1 a) = [(-1,"meta",[],(map fst (map renderAtt a)),[content_byte])]
    tagChildren (Link_1 a) = [(-1,"link",[],(map fst (map renderAtt a)),[])]
    tagChildren (Style_1 a c) = (6,"style",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Script_1 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Object_1 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent2 where
    tagChildren (PCDATA_2 _ _) = []
instance TagChildren Ent3 where
    tagChildren (Script_3 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_3 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_3 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_3 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_3 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_3 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_3 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_3 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_3 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_3 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_3 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_3 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_3 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_3 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_3 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_3 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_3 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_3 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_3 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_3 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_3 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_3 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_3 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_3 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_3 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_3 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_3 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_3 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_3 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_3 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_3 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_3 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_3 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_3 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_3 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_3 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_3 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_3 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_3 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_3 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_3 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_3 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_3 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_3 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_3 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_3 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Label_3 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_3 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_3 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_3 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_3 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_3 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_3 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_3 _ _) = []
instance TagChildren Ent4 where
    tagChildren (Script_4 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_4 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_4 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_4 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_4 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_4 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_4 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_4 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_4 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_4 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_4 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_4 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_4 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_4 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_4 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_4 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_4 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_4 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_4 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_4 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_4 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_4 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_4 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_4 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_4 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_4 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_4 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_4 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_4 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_4 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_4 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_4 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_4 _ _) = []
instance TagChildren Ent5 where
    tagChildren (PCDATA_5 _ _) = []
instance TagChildren Ent6 where
    tagChildren (Script_6 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_6 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_6 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_6 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_6 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_6 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_6 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_6 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_6 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_6 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_6 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_6 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_6 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_6 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_6 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_6 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_6 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_6 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_6 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_6 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_6 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_6 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_6 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_6 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_6 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_6 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_6 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_6 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_6 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_6 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_6 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_6 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_6 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_6 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_6 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_6 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_6 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_6 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_6 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_6 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_6 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_6 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_6 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_6 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Label_6 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_6 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_6 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_6 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_6 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_6 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_6 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_6 _ _) = []
instance TagChildren Ent7 where
    tagChildren (Script_7 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_7 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_7 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_7 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_7 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_7 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_7 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_7 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_7 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_7 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_7 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_7 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_7 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_7 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_7 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_7 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_7 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_7 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_7 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Form_7 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_7 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_7 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent8 where
    tagChildren (Li_8 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent9 where
    tagChildren (Dt_9 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_9 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent10 where
    tagChildren (Script_10 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_10 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_10 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_10 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_10 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_10 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_10 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_10 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_10 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_10 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_10 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_10 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_10 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_10 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_10 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_10 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_10 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_10 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_10 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_10 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_10 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_10 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_10 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_10 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_10 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_10 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_10 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_10 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_10 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_10 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_10 _ _) = []
instance TagChildren Ent11 where
    tagChildren (Script_11 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_11 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_11 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_11 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_11 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_11 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_11 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_11 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_11 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_11 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_11 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_11 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_11 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_11 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_11 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_11 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_11 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_11 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_11 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Fieldset_11 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_11 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent12 where
    tagChildren (Script_12 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_12 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_12 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_12 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_12 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_12 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_12 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_12 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_12 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_12 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_12 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_12 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_12 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_12 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_12 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_12 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_12 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_12 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_12 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_12 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_12 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_12 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_12 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_12 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_12 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_12 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_12 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_12 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_12 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_12 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_12 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_12 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_12 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_12 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_12 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_12 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_12 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_12 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_12 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_12 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_12 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_12 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_12 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_12 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_12 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_12 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_12 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_12 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_12 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_12 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_12 _ _) = []
instance TagChildren Ent13 where
    tagChildren (Script_13 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_13 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_13 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_13 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_13 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_13 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_13 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_13 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_13 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_13 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_13 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_13 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_13 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_13 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_13 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_13 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_13 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_13 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_13 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_13 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_13 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_13 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_13 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_13 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_13 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_13 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_13 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_13 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_13 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_13 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_13 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_13 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_13 _ _) = []
instance TagChildren Ent14 where
    tagChildren (Li_14 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent15 where
    tagChildren (Dt_15 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_15 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent16 where
    tagChildren (Script_16 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_16 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_16 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_16 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_16 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_16 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_16 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_16 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_16 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_16 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_16 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_16 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_16 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_16 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_16 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_16 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_16 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_16 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_16 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_16 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_16 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_16 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_16 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_16 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_16 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_16 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_16 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_16 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_16 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_16 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_16 _ _) = []
instance TagChildren Ent17 where
    tagChildren (Script_17 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_17 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_17 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_17 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_17 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_17 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_17 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_17 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_17 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_17 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_17 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_17 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_17 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_17 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_17 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_17 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_17 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_17 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_17 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_17 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_17 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_17 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_17 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_17 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_17 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_17 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_17 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_17 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_17 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_17 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_17 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_17 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_17 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_17 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_17 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_17 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_17 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_17 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_17 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_17 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_17 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_17 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_17 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_17 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_17 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_17 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_17 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_17 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_17 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_17 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_17 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_17 _ _) = []
instance TagChildren Ent18 where
    tagChildren (Caption_18 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_18 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_18 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_18 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_18 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_18 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_18 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent19 where
    tagChildren (Tr_19 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent20 where
    tagChildren (Col_20 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent21 where
    tagChildren (Th_21 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_21 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent22 where
    tagChildren (Script_22 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_22 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_22 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_22 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_22 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_22 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_22 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_22 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_22 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_22 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_22 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_22 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_22 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_22 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_22 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_22 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_22 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_22 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_22 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_22 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_22 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_22 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_22 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_22 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_22 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_22 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_22 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_22 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_22 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_22 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_22 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_22 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_22 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_22 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_22 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_22 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_22 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_22 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_22 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_22 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_22 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_22 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_22 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_22 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Label_22 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_22 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_22 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_22 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_22 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_22 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_22 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_22 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_22 _ _) = []
instance TagChildren Ent23 where
    tagChildren (Caption_23 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_23 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_23 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_23 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_23 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_23 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_23 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent24 where
    tagChildren (Tr_24 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent25 where
    tagChildren (Col_25 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent26 where
    tagChildren (Th_26 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_26 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent27 where
    tagChildren (Script_27 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_27 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_27 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_27 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_27 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_27 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_27 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_27 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_27 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_27 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_27 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_27 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_27 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_27 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_27 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_27 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_27 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_27 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_27 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_27 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_27 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_27 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_27 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_27 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_27 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_27 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_27 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_27 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_27 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_27 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_27 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_27 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_27 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_27 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_27 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_27 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_27 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_27 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_27 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_27 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_27 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_27 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_27 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_27 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_27 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Label_27 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_27 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_27 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_27 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_27 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_27 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_27 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_27 _ _) = []
instance TagChildren Ent28 where
    tagChildren (Script_28 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_28 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_28 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_28 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_28 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_28 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_28 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_28 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_28 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_28 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_28 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_28 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_28 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_28 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_28 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_28 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_28 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_28 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_28 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_28 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Form_28 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_28 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_28 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent29 where
    tagChildren (Script_29 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_29 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_29 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_29 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_29 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_29 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_29 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_29 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_29 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_29 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_29 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_29 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_29 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_29 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_29 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_29 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_29 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_29 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_29 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_29 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_29 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_29 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_29 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_29 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_29 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_29 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_29 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_29 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_29 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_29 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_29 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_29 _ _) = []
instance TagChildren Ent30 where
    tagChildren (PCDATA_30 _ _) = []
instance TagChildren Ent31 where
    tagChildren (Script_31 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_31 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_31 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_31 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_31 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_31 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_31 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_31 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_31 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_31 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_31 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_31 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_31 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_31 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_31 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_31 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_31 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_31 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_31 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_31 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_31 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_31 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_31 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_31 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_31 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_31 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_31 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_31 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_31 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_31 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_31 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_31 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_31 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_31 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_31 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_31 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_31 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_31 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_31 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_31 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_31 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_31 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_31 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_31 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Input_31 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_31 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_31 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_31 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_31 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_31 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_31 _ _) = []
instance TagChildren Ent32 where
    tagChildren (Script_32 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_32 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_32 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_32 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_32 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_32 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_32 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_32 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_32 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_32 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_32 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_32 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_32 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_32 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_32 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_32 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_32 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_32 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_32 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Form_32 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_32 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_32 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent33 where
    tagChildren (Li_33 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent34 where
    tagChildren (Dt_34 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_34 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent35 where
    tagChildren (Script_35 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_35 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_35 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_35 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_35 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_35 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_35 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_35 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_35 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_35 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_35 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_35 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_35 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_35 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_35 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_35 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_35 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_35 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_35 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_35 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_35 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_35 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_35 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_35 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_35 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_35 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_35 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_35 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_35 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_35 _ _) = []
instance TagChildren Ent36 where
    tagChildren (Script_36 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_36 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_36 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_36 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_36 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_36 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_36 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_36 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_36 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_36 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_36 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_36 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_36 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_36 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_36 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_36 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_36 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_36 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_36 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Fieldset_36 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_36 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent37 where
    tagChildren (Script_37 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_37 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_37 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_37 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_37 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_37 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_37 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_37 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_37 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_37 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_37 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_37 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_37 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_37 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_37 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_37 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_37 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_37 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_37 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_37 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_37 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_37 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_37 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_37 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_37 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_37 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_37 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_37 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_37 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_37 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_37 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_37 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_37 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_37 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_37 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_37 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_37 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_37 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_37 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_37 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_37 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_37 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_37 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_37 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_37 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_37 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_37 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_37 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_37 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_37 _ _) = []
instance TagChildren Ent38 where
    tagChildren (Script_38 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_38 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_38 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_38 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_38 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_38 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_38 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_38 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_38 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_38 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_38 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_38 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_38 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_38 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_38 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_38 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_38 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_38 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_38 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_38 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_38 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_38 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_38 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_38 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_38 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_38 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_38 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_38 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_38 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_38 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_38 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_38 _ _) = []
instance TagChildren Ent39 where
    tagChildren (Li_39 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent40 where
    tagChildren (Dt_40 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_40 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent41 where
    tagChildren (Script_41 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_41 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_41 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_41 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_41 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_41 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_41 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_41 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_41 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_41 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_41 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_41 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_41 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_41 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_41 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_41 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_41 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_41 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_41 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_41 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_41 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_41 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_41 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_41 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_41 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_41 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_41 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_41 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_41 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_41 _ _) = []
instance TagChildren Ent42 where
    tagChildren (Script_42 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_42 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_42 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_42 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_42 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_42 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_42 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_42 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_42 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_42 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_42 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_42 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_42 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_42 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_42 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_42 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_42 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_42 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_42 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_42 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_42 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_42 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_42 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_42 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_42 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_42 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_42 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_42 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_42 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_42 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_42 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_42 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_42 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_42 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_42 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_42 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_42 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_42 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_42 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_42 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_42 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_42 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_42 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_42 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_42 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_42 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_42 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_42 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_42 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_42 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_42 _ _) = []
instance TagChildren Ent43 where
    tagChildren (Caption_43 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_43 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_43 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_43 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_43 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_43 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_43 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent44 where
    tagChildren (Tr_44 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent45 where
    tagChildren (Col_45 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent46 where
    tagChildren (Th_46 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_46 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent47 where
    tagChildren (Script_47 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_47 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_47 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_47 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_47 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_47 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_47 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_47 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_47 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_47 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_47 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_47 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_47 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_47 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_47 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_47 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_47 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_47 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_47 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_47 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_47 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_47 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_47 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_47 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_47 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_47 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_47 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_47 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_47 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_47 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_47 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_47 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_47 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_47 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_47 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_47 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_47 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_47 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_47 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_47 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_47 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_47 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_47 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_47 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Input_47 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_47 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_47 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_47 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_47 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_47 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_47 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_47 _ _) = []
instance TagChildren Ent48 where
    tagChildren (Caption_48 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_48 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_48 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_48 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_48 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_48 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_48 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent49 where
    tagChildren (Tr_49 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent50 where
    tagChildren (Col_50 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent51 where
    tagChildren (Th_51 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_51 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent52 where
    tagChildren (Script_52 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_52 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_52 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_52 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_52 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_52 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_52 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_52 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_52 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_52 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_52 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_52 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_52 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_52 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_52 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_52 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_52 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_52 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_52 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_52 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_52 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_52 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_52 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_52 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_52 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_52 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_52 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_52 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_52 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_52 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_52 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_52 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_52 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_52 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_52 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_52 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_52 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_52 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_52 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_52 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_52 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_52 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_52 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_52 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_52 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Input_52 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_52 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_52 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_52 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_52 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_52 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_52 _ _) = []
instance TagChildren Ent53 where
    tagChildren (Script_53 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_53 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_53 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_53 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_53 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_53 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_53 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_53 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_53 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_53 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_53 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_53 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_53 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_53 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_53 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_53 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_53 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_53 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_53 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_53 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Form_53 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_53 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_53 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent54 where
    tagChildren (Optgroup_54 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_54 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent55 where
    tagChildren (Option_55 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent56 where
    tagChildren (Script_56 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_56 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_56 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_56 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_56 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_56 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_56 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_56 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_56 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_56 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_56 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_56 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_56 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_56 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_56 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_56 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_56 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_56 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_56 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_56 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_56 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_56 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_56 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_56 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_56 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_56 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_56 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_56 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_56 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_56 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_56 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_56 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_56 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_56 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_56 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_56 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_56 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_56 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_56 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_56 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_56 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_56 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_56 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_56 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_56 _ _) = []
instance TagChildren Ent57 where
    tagChildren (Optgroup_57 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_57 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent58 where
    tagChildren (Option_58 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent59 where
    tagChildren (Script_59 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_59 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_59 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_59 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_59 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_59 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_59 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_59 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_59 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_59 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_59 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_59 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_59 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_59 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_59 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_59 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_59 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_59 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_59 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_59 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_59 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_59 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_59 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_59 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_59 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_59 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_59 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_59 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_59 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_59 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_59 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_59 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_59 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_59 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_59 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_59 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_59 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_59 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_59 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_59 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_59 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_59 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_59 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_59 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_59 _ _) = []
instance TagChildren Ent60 where
    tagChildren (Script_60 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_60 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_60 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_60 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_60 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_60 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_60 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_60 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_60 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_60 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_60 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_60 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_60 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_60 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_60 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_60 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_60 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_60 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_60 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_60 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_60 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_60 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_60 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_60 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_60 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_60 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_60 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_60 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_60 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_60 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_60 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_60 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_60 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_60 _ _) = []
instance TagChildren Ent61 where
    tagChildren (Script_61 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_61 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_61 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_61 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_61 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_61 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_61 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_61 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_61 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_61 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_61 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_61 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_61 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_61 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_61 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_61 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_61 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_61 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_61 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_61 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Form_61 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_61 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_61 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent62 where
    tagChildren (Script_62 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_62 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_62 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_62 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_62 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_62 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_62 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_62 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_62 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_62 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_62 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_62 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_62 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_62 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_62 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_62 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_62 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_62 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_62 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_62 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_62 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_62 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_62 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_62 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_62 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_62 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_62 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_62 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_62 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_62 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_62 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_62 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_62 _ _) = []
instance TagChildren Ent63 where
    tagChildren (PCDATA_63 _ _) = []
instance TagChildren Ent64 where
    tagChildren (Script_64 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_64 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_64 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_64 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_64 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_64 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_64 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_64 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_64 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_64 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_64 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_64 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_64 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_64 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_64 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_64 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_64 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_64 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_64 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_64 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_64 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_64 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_64 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_64 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_64 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_64 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_64 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_64 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_64 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_64 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_64 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_64 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_64 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_64 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_64 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_64 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_64 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_64 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_64 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_64 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_64 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_64 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_64 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_64 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_64 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Input_64 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_64 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_64 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_64 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_64 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_64 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_64 _ _) = []
instance TagChildren Ent65 where
    tagChildren (Script_65 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_65 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_65 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_65 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_65 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_65 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_65 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_65 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_65 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_65 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_65 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_65 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_65 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_65 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_65 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_65 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_65 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_65 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_65 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Form_65 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_65 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_65 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent66 where
    tagChildren (Li_66 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent67 where
    tagChildren (Dt_67 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_67 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent68 where
    tagChildren (Script_68 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_68 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_68 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_68 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_68 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_68 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_68 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_68 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_68 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_68 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_68 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_68 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_68 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_68 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_68 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_68 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_68 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_68 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_68 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_68 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_68 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_68 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_68 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_68 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_68 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_68 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_68 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_68 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_68 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_68 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_68 _ _) = []
instance TagChildren Ent69 where
    tagChildren (Script_69 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_69 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_69 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_69 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_69 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_69 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_69 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_69 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_69 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_69 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_69 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_69 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_69 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_69 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_69 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_69 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_69 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_69 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_69 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Fieldset_69 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_69 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent70 where
    tagChildren (Script_70 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_70 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_70 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_70 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_70 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_70 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_70 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_70 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_70 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_70 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_70 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_70 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_70 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_70 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_70 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_70 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_70 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_70 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_70 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_70 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_70 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_70 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_70 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_70 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_70 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_70 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_70 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_70 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_70 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_70 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_70 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_70 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_70 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_70 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_70 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_70 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_70 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_70 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_70 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_70 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_70 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_70 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_70 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_70 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_70 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_70 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_70 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_70 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_70 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_70 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_70 _ _) = []
instance TagChildren Ent71 where
    tagChildren (Script_71 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_71 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_71 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_71 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_71 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_71 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_71 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_71 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_71 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_71 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_71 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_71 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_71 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_71 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_71 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_71 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_71 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_71 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_71 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_71 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_71 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_71 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_71 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_71 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_71 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_71 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_71 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_71 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_71 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_71 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_71 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_71 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_71 _ _) = []
instance TagChildren Ent72 where
    tagChildren (Li_72 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent73 where
    tagChildren (Dt_73 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_73 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent74 where
    tagChildren (Script_74 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_74 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_74 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_74 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_74 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_74 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_74 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_74 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_74 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_74 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_74 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_74 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_74 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_74 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_74 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_74 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_74 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_74 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_74 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_74 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_74 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_74 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_74 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_74 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_74 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_74 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_74 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_74 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_74 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_74 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_74 _ _) = []
instance TagChildren Ent75 where
    tagChildren (Script_75 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_75 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_75 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_75 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_75 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_75 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_75 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_75 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_75 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_75 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_75 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_75 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_75 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_75 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_75 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_75 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_75 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_75 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_75 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_75 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_75 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_75 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_75 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_75 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_75 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_75 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_75 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_75 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_75 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_75 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_75 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_75 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_75 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_75 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_75 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_75 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_75 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_75 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_75 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_75 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_75 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_75 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_75 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_75 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_75 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_75 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_75 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_75 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_75 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_75 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_75 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_75 _ _) = []
instance TagChildren Ent76 where
    tagChildren (Caption_76 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_76 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_76 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_76 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_76 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_76 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_76 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent77 where
    tagChildren (Tr_77 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent78 where
    tagChildren (Col_78 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent79 where
    tagChildren (Th_79 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_79 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent80 where
    tagChildren (Script_80 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_80 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_80 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_80 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_80 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_80 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_80 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_80 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_80 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_80 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_80 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_80 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_80 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_80 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_80 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_80 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_80 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_80 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_80 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_80 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_80 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_80 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_80 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_80 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_80 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_80 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_80 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_80 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_80 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_80 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_80 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_80 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_80 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_80 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_80 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_80 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_80 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_80 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_80 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_80 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_80 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_80 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_80 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_80 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_80 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Input_80 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_80 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_80 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_80 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_80 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_80 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_80 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_80 _ _) = []
instance TagChildren Ent81 where
    tagChildren (Caption_81 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_81 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_81 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_81 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_81 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_81 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_81 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent82 where
    tagChildren (Tr_82 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent83 where
    tagChildren (Col_83 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent84 where
    tagChildren (Th_84 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_84 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent85 where
    tagChildren (Script_85 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_85 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_85 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_85 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_85 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_85 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_85 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_85 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_85 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_85 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_85 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_85 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_85 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_85 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_85 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_85 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_85 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_85 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_85 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_85 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_85 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_85 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_85 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_85 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_85 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_85 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_85 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_85 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_85 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_85 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_85 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_85 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_85 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_85 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_85 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_85 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_85 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_85 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_85 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_85 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_85 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_85 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_85 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_85 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_85 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_85 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Input_85 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_85 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_85 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_85 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_85 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_85 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_85 _ _) = []
instance TagChildren Ent86 where
    tagChildren (Script_86 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_86 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_86 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_86 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_86 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_86 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_86 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_86 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_86 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_86 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_86 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_86 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_86 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_86 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_86 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_86 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_86 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_86 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_86 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_86 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Form_86 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_86 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_86 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent87 where
    tagChildren (Optgroup_87 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_87 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent88 where
    tagChildren (Option_88 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent89 where
    tagChildren (Script_89 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_89 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_89 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_89 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_89 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_89 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_89 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_89 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_89 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_89 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_89 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_89 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_89 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_89 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_89 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_89 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_89 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_89 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_89 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_89 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_89 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_89 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_89 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_89 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_89 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_89 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_89 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_89 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_89 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_89 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_89 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_89 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_89 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_89 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_89 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_89 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_89 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_89 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_89 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_89 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_89 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_89 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_89 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_89 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_89 _ _) = []
instance TagChildren Ent90 where
    tagChildren (Optgroup_90 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_90 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent91 where
    tagChildren (Option_91 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent92 where
    tagChildren (Script_92 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_92 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_92 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_92 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_92 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_92 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_92 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_92 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_92 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_92 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_92 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_92 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_92 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_92 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_92 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_92 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_92 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_92 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_92 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_92 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_92 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_92 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_92 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_92 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_92 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_92 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_92 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_92 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_92 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_92 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_92 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_92 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_92 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_92 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_92 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_92 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_92 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_92 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_92 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_92 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_92 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_92 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_92 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_92 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_92 _ _) = []
instance TagChildren Ent93 where
    tagChildren (Script_93 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_93 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_93 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_93 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_93 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_93 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_93 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_93 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_93 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_93 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_93 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_93 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_93 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_93 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_93 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_93 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_93 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_93 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_93 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Form_93 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_93 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_93 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent94 where
    tagChildren (Script_94 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_94 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_94 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_94 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_94 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_94 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_94 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_94 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_94 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_94 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_94 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_94 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_94 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_94 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_94 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_94 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_94 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_94 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_94 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_94 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_94 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_94 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_94 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_94 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_94 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_94 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_94 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_94 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_94 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_94 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_94 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_94 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_94 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_94 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_94 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_94 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_94 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_94 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_94 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_94 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_94 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_94 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_94 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_94 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_94 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Label_94 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_94 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_94 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_94 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_94 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_94 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_94 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_94 _ _) = []
instance TagChildren Ent95 where
    tagChildren (Li_95 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent96 where
    tagChildren (Dt_96 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_96 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent97 where
    tagChildren (Script_97 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_97 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_97 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_97 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_97 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_97 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_97 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_97 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_97 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_97 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_97 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_97 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_97 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_97 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_97 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_97 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_97 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_97 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_97 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_97 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_97 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_97 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_97 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_97 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_97 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_97 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_97 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_97 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_97 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_97 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_97 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_97 _ _) = []
instance TagChildren Ent98 where
    tagChildren (Script_98 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_98 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_98 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_98 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_98 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_98 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_98 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_98 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_98 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_98 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_98 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_98 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_98 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_98 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_98 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_98 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_98 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_98 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_98 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Fieldset_98 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_98 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent99 where
    tagChildren (PCDATA_99 _ _) = []
instance TagChildren Ent100 where
    tagChildren (Script_100 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_100 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_100 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_100 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_100 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_100 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_100 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_100 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_100 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_100 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_100 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_100 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_100 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_100 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_100 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_100 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_100 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_100 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_100 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_100 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_100 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_100 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_100 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_100 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_100 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_100 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_100 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_100 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_100 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_100 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_100 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_100 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_100 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_100 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_100 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_100 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_100 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_100 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_100 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_100 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_100 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_100 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_100 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_100 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_100 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_100 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_100 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_100 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_100 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_100 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_100 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_100 _ _) = []
instance TagChildren Ent101 where
    tagChildren (PCDATA_101 _ _) = []
instance TagChildren Ent102 where
    tagChildren (Script_102 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_102 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_102 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_102 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_102 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_102 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_102 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_102 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_102 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_102 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_102 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_102 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_102 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_102 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_102 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_102 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_102 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_102 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_102 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_102 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_102 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_102 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_102 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_102 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_102 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_102 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_102 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_102 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_102 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_102 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_102 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_102 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_102 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_102 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_102 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_102 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_102 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_102 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_102 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_102 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_102 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_102 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_102 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_102 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_102 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_102 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_102 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_102 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_102 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_102 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_102 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_102 _ _) = []
instance TagChildren Ent103 where
    tagChildren (Script_103 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_103 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_103 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_103 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_103 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_103 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_103 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_103 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_103 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_103 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_103 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_103 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_103 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_103 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_103 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_103 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_103 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_103 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_103 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_103 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Fieldset_103 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_103 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent104 where
    tagChildren (PCDATA_104 _ _) = []
instance TagChildren Ent105 where
    tagChildren (Script_105 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_105 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_105 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_105 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_105 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_105 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_105 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_105 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_105 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_105 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_105 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_105 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_105 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_105 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_105 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_105 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_105 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_105 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_105 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_105 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_105 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_105 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_105 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_105 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_105 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_105 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_105 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_105 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_105 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_105 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_105 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_105 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_105 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_105 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_105 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_105 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_105 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_105 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_105 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_105 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_105 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_105 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_105 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_105 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_105 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_105 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_105 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_105 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_105 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_105 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_105 _ _) = []
instance TagChildren Ent106 where
    tagChildren (Script_106 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_106 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_106 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_106 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_106 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_106 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_106 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_106 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_106 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_106 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_106 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_106 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_106 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_106 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_106 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_106 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_106 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_106 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_106 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_106 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Fieldset_106 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_106 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent107 where
    tagChildren (Optgroup_107 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_107 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent108 where
    tagChildren (Option_108 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent109 where
    tagChildren (Script_109 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_109 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_109 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_109 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_109 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_109 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_109 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_109 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_109 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_109 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_109 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_109 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_109 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_109 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_109 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_109 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_109 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_109 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_109 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_109 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_109 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_109 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_109 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_109 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_109 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_109 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_109 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_109 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_109 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_109 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_109 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_109 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_109 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_109 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_109 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_109 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_109 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_109 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_109 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_109 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_109 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_109 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_109 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_109 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_109 _ _) = []
instance TagChildren Ent110 where
    tagChildren (Optgroup_110 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_110 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent111 where
    tagChildren (Option_111 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent112 where
    tagChildren (Script_112 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_112 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_112 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_112 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_112 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_112 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_112 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_112 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_112 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_112 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_112 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_112 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_112 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_112 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_112 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_112 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_112 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_112 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_112 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_112 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_112 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_112 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_112 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_112 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_112 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_112 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_112 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_112 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_112 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_112 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_112 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_112 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_112 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_112 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_112 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_112 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_112 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_112 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_112 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_112 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_112 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_112 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_112 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_112 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_112 _ _) = []
instance TagChildren Ent113 where
    tagChildren (Script_113 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_113 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_113 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_113 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_113 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_113 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_113 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_113 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_113 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_113 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_113 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_113 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_113 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_113 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_113 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_113 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_113 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_113 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_113 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_113 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_113 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_113 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_113 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_113 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_113 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_113 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_113 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_113 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_113 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_113 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_113 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_113 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_113 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_113 _ _) = []
instance TagChildren Ent114 where
    tagChildren (Script_114 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_114 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_114 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_114 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_114 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_114 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_114 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_114 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_114 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_114 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_114 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_114 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_114 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_114 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_114 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_114 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_114 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_114 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_114 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_114 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_114 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_114 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_114 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_114 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_114 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_114 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_114 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_114 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_114 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_114 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_114 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_114 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_114 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_114 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_114 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_114 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_114 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_114 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_114 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_114 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_114 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_114 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_114 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_114 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_114 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_114 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_114 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_114 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_114 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_114 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_114 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_114 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_114 _ _) = []
instance TagChildren Ent115 where
    tagChildren (Script_115 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_115 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_115 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_115 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_115 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_115 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_115 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_115 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_115 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_115 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_115 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_115 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_115 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_115 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_115 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_115 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_115 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_115 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_115 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_115 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Fieldset_115 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_115 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent116 where
    tagChildren (PCDATA_116 _ _) = []
instance TagChildren Ent117 where
    tagChildren (Script_117 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_117 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_117 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_117 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_117 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_117 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_117 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_117 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_117 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_117 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_117 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_117 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_117 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_117 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_117 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_117 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_117 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_117 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_117 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_117 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_117 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_117 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_117 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_117 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_117 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_117 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_117 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_117 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_117 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_117 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_117 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_117 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_117 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_117 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_117 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_117 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_117 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_117 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_117 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_117 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_117 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_117 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Param_117 a) = [(-1,"param",[],(map fst (map renderAtt a)),[])]
    tagChildren (Img_117 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_117 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Input_117 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_117 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_117 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_117 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_117 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_117 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_117 _ _) = []
instance TagChildren Ent118 where
    tagChildren (Script_118 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_118 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_118 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_118 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_118 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_118 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_118 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_118 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_118 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_118 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_118 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_118 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_118 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_118 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_118 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_118 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_118 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_118 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_118 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Area_118 a) = [(-1,"area",[],(map fst (map renderAtt a)),[alt_byte])]
    tagChildren (Fieldset_118 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_118 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent119 where
    tagChildren (Optgroup_119 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_119 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent120 where
    tagChildren (Option_120 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent121 where
    tagChildren (Script_121 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_121 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_121 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_121 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_121 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_121 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_121 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_121 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_121 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_121 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_121 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_121 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_121 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_121 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_121 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_121 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_121 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_121 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_121 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_121 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_121 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_121 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_121 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_121 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_121 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_121 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_121 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_121 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_121 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_121 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_121 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_121 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_121 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_121 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_121 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_121 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_121 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_121 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_121 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_121 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_121 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_121 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_121 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_121 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_121 _ _) = []
instance TagChildren Ent122 where
    tagChildren (Optgroup_122 a c) = (61,"optgroup",map tagStr c,(map fst (map renderAtt a)),[label_byte]):(concatMap tagChildren c)
    tagChildren (Option_122 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent123 where
    tagChildren (Option_123 a c) = (62,"option",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent124 where
    tagChildren (Script_124 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_124 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_124 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_124 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_124 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_124 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_124 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_124 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_124 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_124 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_124 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_124 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_124 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_124 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_124 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_124 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_124 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_124 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_124 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_124 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_124 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_124 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_124 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_124 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_124 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_124 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_124 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_124 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_124 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_124 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_124 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_124 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_124 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_124 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_124 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_124 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_124 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_124 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_124 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_124 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_124 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_124 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_124 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Table_124 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_124 _ _) = []
instance TagChildren Ent125 where
    tagChildren (Li_125 a c) = (20,"li",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent126 where
    tagChildren (Dt_126 a c) = (22,"dt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dd_126 a c) = (23,"dd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent127 where
    tagChildren (Script_127 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Ins_127 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_127 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_127 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_127 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_127 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_127 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_127 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_127 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_127 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_127 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_127 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_127 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_127 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_127 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_127 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_127 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_127 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_127 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_127 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_127 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_127 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_127 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_127 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_127 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Map_127 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_127 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_127 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_127 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_127 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Button_127 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_127 _ _) = []
instance TagChildren Ent128 where
    tagChildren (Script_128 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_128 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_128 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_128 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_128 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_128 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_128 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_128 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_128 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_128 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_128 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_128 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_128 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_128 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_128 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_128 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_128 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_128 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_128 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_128 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_128 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_128 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_128 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_128 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_128 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_128 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_128 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_128 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_128 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_128 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_128 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_128 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_128 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_128 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_128 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_128 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_128 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_128 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_128 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_128 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_128 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_128 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_128 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_128 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Label_128 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_128 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_128 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_128 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_128 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_128 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_128 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_128 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_128 _ _) = []
instance TagChildren Ent129 where
    tagChildren (Caption_129 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_129 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_129 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_129 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_129 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_129 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_129 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent130 where
    tagChildren (Tr_130 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent131 where
    tagChildren (Col_131 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent132 where
    tagChildren (Th_132 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_132 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent133 where
    tagChildren (Script_133 a c) = (7,"script",map tagStr c,(map fst (map renderAtt a)),[type_byte]):(concatMap tagChildren c)
    tagChildren (Noscript_133 a c) = (8,"noscript",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Div_133 a c) = (10,"div",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (P_133 a c) = (11,"p",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H1_133 a c) = (12,"h1",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H2_133 a c) = (13,"h2",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H3_133 a c) = (14,"h3",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H4_133 a c) = (15,"h4",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H5_133 a c) = (16,"h5",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (H6_133 a c) = (17,"h6",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ul_133 a c) = (18,"ul",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ol_133 a c) = (19,"ol",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dl_133 a c) = (21,"dl",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Address_133 a c) = (24,"address",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Hr_133 a) = [(-1,"hr",[],(map fst (map renderAtt a)),[])]
    tagChildren (Pre_133 a c) = (26,"pre",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Blockquote_133 a c) = (27,"blockquote",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Ins_133 a c) = (28,"ins",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Del_133 a c) = (29,"del",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (A_133 a c) = (30,"a",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Span_133 a c) = (31,"span",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Bdo_133 a c) = (32,"bdo",map tagStr c,(map fst (map renderAtt a)),[dir_byte]):(concatMap tagChildren c)
    tagChildren (Br_133 a) = [(-1,"br",[],(map fst (map renderAtt a)),[])]
    tagChildren (Em_133 a c) = (34,"em",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Strong_133 a c) = (35,"strong",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Dfn_133 a c) = (36,"dfn",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Code_133 a c) = (37,"code",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Samp_133 a c) = (38,"samp",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Kbd_133 a c) = (39,"kbd",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Var_133 a c) = (40,"var",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Cite_133 a c) = (41,"cite",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Abbr_133 a c) = (42,"abbr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Acronym_133 a c) = (43,"acronym",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Q_133 a c) = (44,"q",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sub_133 a c) = (45,"sub",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Sup_133 a c) = (46,"sup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tt_133 a c) = (47,"tt",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (I_133 a c) = (48,"i",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (B_133 a c) = (49,"b",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Big_133 a c) = (50,"big",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Small_133 a c) = (51,"small",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Object_133 a c) = (52,"object",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Img_133 a) = [(-1,"img",[],(map fst (map renderAtt a)),[src_byte,alt_byte])]
    tagChildren (Map_133 a c) = (55,"map",map tagStr c,(map fst (map renderAtt a)),[id_byte]):(concatMap tagChildren c)
    tagChildren (Form_133 a c) = (57,"form",map tagStr c,(map fst (map renderAtt a)),[action_byte]):(concatMap tagChildren c)
    tagChildren (Label_133 a c) = (58,"label",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Input_133 a) = [(-1,"input",[],(map fst (map renderAtt a)),[])]
    tagChildren (Select_133 a c) = (60,"select",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Textarea_133 a c) = (63,"textarea",map tagStr c,(map fst (map renderAtt a)),[rows_byte,cols_byte]):(concatMap tagChildren c)
    tagChildren (Fieldset_133 a c) = (64,"fieldset",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Legend_133 a c) = (65,"legend",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Button_133 a c) = (66,"button",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Table_133 a c) = (67,"table",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (PCDATA_133 _ _) = []
instance TagChildren Ent134 where
    tagChildren (Caption_134 a c) = (68,"caption",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Thead_134 a c) = (69,"thead",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tfoot_134 a c) = (70,"tfoot",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Tbody_134 a c) = (71,"tbody",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Colgroup_134 a c) = (72,"colgroup",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Col_134 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
    tagChildren (Tr_134 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent135 where
    tagChildren (Tr_135 a c) = (74,"tr",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
instance TagChildren Ent136 where
    tagChildren (Col_136 a) = [(-1,"col",[],(map fst (map renderAtt a)),[])]
instance TagChildren Ent137 where
    tagChildren (Th_137 a c) = (75,"th",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)
    tagChildren (Td_137 a c) = (76,"td",map tagStr c,(map fst (map renderAtt a)),[]):(concatMap tagChildren c)

allowchildren = [("html",(parseRegex "((head)(body))"),"(head,body)"),("head",(parseRegex "(((script)|(style)|(meta)|(link)|(object))*(((title)((script)|(style)|(meta)|(link)|(object))*((base)((script)|(style)|(meta)|(link)|(object))*)?)|((base)((script)|(style)|(meta)|(link)|(object))*((title)((script)|(style)|(meta)|(link)|(object))*))))"),"((script|style|meta|link|object)*,((title,(script|style|meta|link|object)*,(base,(script|style|meta|link|object)*)?)|(base,(script|style|meta|link|object)*,(title,(script|style|meta|link|object)*))))"),("title",(parseRegex "(pcdata)"),"(#pcdata)"),("base",(parseRegex "empty"),"empty"),("meta",(parseRegex "empty"),"empty"),("link",(parseRegex "empty"),"empty"),("style",(parseRegex "(pcdata)"),"(#pcdata)"),("script",(parseRegex "(pcdata)"),"(#pcdata)"),("noscript",(parseRegex "((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))*"),"(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)*"),("body",(parseRegex "((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))*"),"(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)*"),("div",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("p",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h1",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h2",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h3",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h4",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h5",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("h6",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("ul",(parseRegex "((li))+"),"(li)+"),("ol",(parseRegex "((li))+"),"(li)+"),("li",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("dl",(parseRegex "((dt)|(dd))+"),"(dt|dd)+"),("dt",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("dd",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("address",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("hr",(parseRegex "empty"),"empty"),("pre",(parseRegex "(pcdata|(a)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(br)|(span)|(bdo)|(map)|(ins)|(del)|(script)|(input)|(select)|(textarea)|(label)|(button))*"),"(#pcdata|a|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|br|span|bdo|map|ins|del|script|input|select|textarea|label|button)*"),("blockquote",(parseRegex "((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))*"),"(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)*"),("ins",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("del",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("a",(parseRegex "(pcdata|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("span",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("bdo",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("br",(parseRegex "empty"),"empty"),("em",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("strong",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("dfn",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("code",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("samp",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("kbd",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("var",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("cite",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("abbr",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("acronym",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("q",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("sub",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("sup",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("tt",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("i",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("b",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("big",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("small",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("object",(parseRegex "(pcdata|(param)|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|param|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("param",(parseRegex "empty"),"empty"),("img",(parseRegex "empty"),"empty"),("map",(parseRegex "(((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(noscript)|(ins)|(del)|(script))+|(area)+)"),"((p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|noscript|ins|del|script)+|area+)"),("area",(parseRegex "empty"),"empty"),("form",(parseRegex "((p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(noscript)|(ins)|(del)|(script))*"),"(p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|noscript|ins|del|script)*"),("label",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("input",(parseRegex "empty"),"empty"),("select",(parseRegex "((optgroup)|(option))+"),"(optgroup|option)+"),("optgroup",(parseRegex "((option))+"),"(option)+"),("option",(parseRegex "(pcdata)"),"(#pcdata)"),("textarea",(parseRegex "(pcdata)"),"(#pcdata)"),("fieldset",(parseRegex "(pcdata|(legend)|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|legend|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("legend",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("button",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(table)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|table|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|noscript|ins|del|script)*"),("table",(parseRegex "((caption)?((col)*|(colgroup)*)(thead)?(tfoot)?((tbody)+|(tr)+))"),"(caption?,(col*|colgroup*),thead?,tfoot?,(tbody+|tr+))"),("caption",(parseRegex "(pcdata|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(ins)|(del)|(script))*"),"(#pcdata|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|ins|del|script)*"),("thead",(parseRegex "((tr))+"),"(tr)+"),("tfoot",(parseRegex "((tr))+"),"(tr)+"),("tbody",(parseRegex "((tr))+"),"(tr)+"),("colgroup",(parseRegex "((col))*"),"(col)*"),("col",(parseRegex "empty"),"empty"),("tr",(parseRegex "((th)|(td))+"),"(th|td)+"),("th",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("td",(parseRegex "(pcdata|(p)|(h1)|(h2)|(h3)|(h4)|(h5)|(h6)|(div)|(ul)|(ol)|(dl)|(pre)|(hr)|(blockquote)|(address)|(fieldset)|(table)|(form)|(a)|(br)|(span)|(bdo)|(map)|(object)|(img)|(tt)|(i)|(b)|(big)|(small)|(em)|(strong)|(dfn)|(code)|(q)|(samp)|(kbd)|(var)|(cite)|(abbr)|(acronym)|(sub)|(sup)|(input)|(select)|(textarea)|(label)|(button)|(noscript)|(ins)|(del)|(script))*"),"(#pcdata|p|h1|h2|h3|h4|h5|h6|div|ul|ol|dl|pre|hr|blockquote|address|fieldset|table|form|a|br|span|bdo|map|object|img|tt|i|b|big|small|em|strong|dfn|code|q|samp|kbd|var|cite|abbr|acronym|sub|sup|input|select|textarea|label|button|noscript|ins|del|script)*"),("", parseRegex "", "")]
-- 'pageErrors' will return any compliance errors, currently tag ordering errors, tag existance errors, or missing required attributes.
-- 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.
-- > pageErrors (_html [])
-- > = ["'html' tag error due to children: .  Must fit (head,body)"]
-- Returns an error because no children were declared for the html tag where <head> and <body> must be children in that order.
pageErrors :: TagChildren a => a -> [String]
pageErrors = childErrors
childErrors :: TagChildren a => a -> [String]
childErrors a = childErrorsHelp (tagChildren a)

validate :: (Int,String) ->  Bool
validate (ti,children)
    | ti == -1 = True
    | result == False = False
    | otherwise = True
                  where
                    (t,regex,raw) =  allowchildren !! ti
                    result = matchRE regex children 
                    
validateAtts :: [U.ByteString] -> [U.ByteString] -> (Bool,String)
validateAtts provided required
    | False = (True,"")
    | otherwise = (False,concat (intersperse ", " (map (\a->a ++ " required!")  diff)))
            where 
             diff = ((map U.toString required) \\ (map U.toString provided))

childErrorsHelp :: [(Int,String,[String],[U.ByteString],[U.ByteString])] -> [String]
childErrorsHelp [] = []
childErrorsHelp ((ti,tag,children,atts,ratts):xs)
    | validate (ti,concat children) = (childErrorsHelp xs) ++ attfixuse
    | otherwise = ("'" ++ tag ++ "' tag error due to incorrect children: " ++ (concat (intersperse "-"  children)) ++ ".  Must fit " ++ raw):( (childErrorsHelp xs) ++ attfixuse)    
        where (t,regex,raw) = allowchildren !! ti
              (validatts,attfix) = validateAtts atts ratts
              attfixuse = if null attfix then
                            [] else
                            ["'" ++ tag ++ "' tag attribute error: " ++ attfix]