module Scanner(tokens, Token(..), nameOfTag, Tag(..), Attr(..), TagAttr(..), attrToTagAttr ) where import Char (isSpace, toLower) import List (elem, elemIndex, lookup, partition) import Alex import Unicode data MyState = MyState { commentDepth :: Integer, inPre :: Bool, currentTagName :: String, allowedAttrs :: [Attr] } tokens :: String -> [Token] tokens inp = gscan hdoc_scan (MyState { commentDepth=0, inPre=False, currentTagName="", allowedAttrs=[] } ) inp hdoc_scan :: GScan MyState [Token] hdoc_scan = load_gscan (hdoc_acts, stop_act) hdoc_lx where -- when the scanner stops with start code "hd3" and the remaining -- input "" or "\n" then we need to add a EndHDoc token as the -- rule "^n %b ^-^- / ~^-" can't detect the end of the HDoc comment! stop_act p _ "" (sc,_) | sc `elem` [hd3, hd3Ty] = [EndHDoc p ""] | otherwise = [] stop_act p@(Pn addr ln col) _ inp (sc,_) | sc `elem` [hd3, hd3Ty] && inp == "\n" = [EndHDoc p inp] | otherwise = [ScanError msg] where msg = "scan error in line " ++ show ln ++ " before\n" ++ " " ++ take 80 inp setStartCode :: StartCode -> GTokenAction s r setStartCode newSC _ _ _ _ cont (_,state) = cont (newSC,state) string = setStartCode str endstring = setStartCode 0 comment _ _ _ _ cont (sc,state) = cont (com, state {commentDepth=1}) comment2 _ _ _ _ cont (sc,state) = cont (sc, state {commentDepth = commentDepth state + 1}) endcomment _ _ _ _ cont (sc, state) = if commentDepth state == 1 then cont (0, state {commentDepth = 0}) else cont (com, state {commentDepth = commentDepth state - 1}) hdocOld = gTkn BeginHDoc hd hdocOldw = gTkn BeginHDoc hd endHDocOld = gTkn EndHDoc 0 newline p _ inp len cont st@(sc,s) | inPre s = SText p inp "\n" : cont st | otherwise = SWhiteSpace p inp : cont st hdocCons1 = gTkn BeginHDocCons hd3 hdocCons2 = gTkn BeginHDocCons hd3 hdoc3 = gTkn BeginHDoc hd3 hdoc3w = gTkn BeginHDoc hd3 endhdoc3 = gTkn EndHDoc 0 newline3 p _ inp len cont st@(sc,s) | inPre s = SText p inp "\n" : cont st | otherwise = SWhiteSpace p inp : cont st newline3w p _ inp len cont st@(sc,s) | inPre s = SText p inp ('\n':w) : cont st | otherwise = SWhiteSpace p inp : cont st where w = drop 2 $ dropWhile isSpace $ take len inp blank p _ inp len cont st@(sc,s) | inPre s = SText p inp (take len inp) : cont st | otherwise = SWhiteSpace p inp : cont st textOldM = text textOld = text text p _ inp len cont s = SText p inp (take len inp) : cont s extSym p _ inp len cont s = SUnicode p inp q : cont s where Just q = lookup (take len inp) sym2u >>= html2unicode sym2u = [("\"", """), ("<", "<"), (">", ">")] namedSymbol p@(Pn _ ln col) _ inp len cont s = symbolToken : cont s where symbolToken = case html2unicode (take len inp) of Just uc -> SUnicode p inp uc Nothing -> ScanError ("scan error in line " ++ show ln ++ ":\n " ++ take len inp ++ " is unknown to HDoc") pre p _ inp len cont (sc,s) = BeginTag p inp PreTag : cont (sc, s {inPre=True}) endpre p _ inp len cont (sc,s) = EndTag p inp PreTag : cont (sc, s{inPre=False}) br = sTkn SBr tag p _ inp len cont (sc,state) = case lookup tagName tagNames of Just t -> BeginTag p inp t : cont (toTag sc, state { currentTagName = tagName, allowedAttrs = allowed }) where Just allowed = lookup t tagAttrs Nothing -> ScanError ("unknown HTML tag <" ++ tagName ++ ">") : cont (toTag sc, state { currentTagName = "(unknown tag)", allowedAttrs = allAttrs }) where tagName = map toLower $ take (len-1) $ drop 1 inp tagAttrName p _ inp len cont s@(sc,state) = case lookup attrName attrNames of Nothing -> ScanError ("unknown attribute `" ++ attrName ++ "'") : cont s Just attr -> if attr `elem` allowedAttrs state then TagAttr p inp attr : cont s else ScanError ("attribute `" ++ attrName ++ "' not allowed\ \ with tag <" ++ currentTagName state ++ ">") : cont s where attrName = map toLower $ take len inp tagEq = sTkn TagAttrEq tagAttrValue p _ inp len cont s = TagAttrValue p inp (take (len-2) $ drop 1 inp) : cont s tagClose p _ inp len cont (sc,state) = {-CloseTag p inp :-} cont (fromTag sc, state { currentTagName="", allowedAttrs=[] }) tagEnd p _ inp len cont s = case lookup tagName tagNames of Just t -> EndTag p inp t : cont s Nothing -> ScanError ("unknown HTML tag ") : cont s where tagName = take (len-3) $ drop 2 inp atcons = jTkn AtCons toTy atparam = jTkn AtParam toTy atret = jTkn AtReturn toTy atmona = jTkn AtMonadic toTy atauthor = sTkn AtAuthor atversion = sTkn AtVersion atsee = atsee3 atsee3 p _ inp len cont s = AtSee p inp ident : cont s where ident = takeWhile (not . isSpace) $ dropZ $ drop 4 $ take len inp atdoc = atdoc3 atdoc3 p _ inp len cont s = AtDoc p inp ident : cont s where ident = takeWhile (not . isSpace) $ dropZ $ drop 4 $ take len inp arrow = sTkn Arrow implies = sTkn Implies ht = sTkn HasType comma = sTkn Comma oparen = sTkn OParen cparen = sTkn CParen obrack = sTkn OBracket cbrack = sTkn CBracket obrace = sTkn OBrace cbrace = sTkn CBrace docFollows = mapMode fromTy backToHd = mapMode fromTy -- skip %z -- ("-- --" would also be skipped, but %z doesn't match that) dropZ :: String -> String dropZ "" = "" dropZ ('-':'-':xs) = dropZ xs dropZ str@(x:xs) | isSpace x = dropZ xs | otherwise = str ident posn _ inp len cont st = Ident posn inp (take len inp) : cont st name posn _ inp len cont st = Conid posn inp (take len inp) : cont st gTkn :: (Posn -> String -> Token) -> StartCode -> GTokenAction MyState [Token] gTkn tfn newSC posn _ inp _ cont (_,s) = tfn posn inp : cont (newSC, s) jTkn :: (Posn -> String -> Token) -> (StartCode -> StartCode) -> GTokenAction MyState [Token] jTkn tfn f posn _ inp _ cont (sc,s) = tfn posn inp : cont (f sc, s) sTkn tfn posn _ inp _ cont st = tfn posn inp : cont st setMode mode _ _ _ _ cont (_,s) = cont (mode, s) mapMode f _ _ _ _ cont (sc,s) = cont (f sc, s) toTy :: StartCode -> StartCode toTy sc | sc == hd3 = hd3Ty | sc == hd = hdTy | otherwise = error "internal error in scanner: unexpected start code ?!" fromTy :: StartCode -> StartCode fromTy sc | sc == hd3Ty = hd3 | sc == hdTy = hd | otherwise = error "internal error in scanner: unexpected start code ?!" toTag :: StartCode -> StartCode toTag sc | sc == hd3 = hd3Tag | sc == hd = hdTag | otherwise = error "internal error in scanner: unexpected start code ?!" fromTag :: StartCode -> StartCode fromTag sc | sc == hd3Tag = hd3 | sc == hdTag = hd | otherwise = error "internal error in scanner: unexpected start code ?!" data Token = BeginHDoc { pos :: Posn, remainingInput :: String } | EndHDoc { pos :: Posn, remainingInput :: String } | BeginHDocCons { pos :: Posn, remainingInput :: String } | AtCons { pos :: Posn, remainingInput :: String } | AtParam { pos :: Posn, remainingInput :: String } | AtReturn { pos :: Posn, remainingInput :: String } | AtMonadic { pos :: Posn, remainingInput :: String } | Ident { pos :: Posn, remainingInput :: String, value :: String } | Conid { pos :: Posn, remainingInput :: String, value :: String } | Arrow { pos :: Posn, remainingInput :: String } | Implies { pos :: Posn, remainingInput :: String } | HasType { pos :: Posn, remainingInput :: String } | Comma { pos :: Posn, remainingInput :: String } | OParen { pos :: Posn, remainingInput :: String } | CParen { pos :: Posn, remainingInput :: String } | OBracket { pos :: Posn, remainingInput :: String } | CBracket { pos :: Posn, remainingInput :: String } | OBrace { pos :: Posn, remainingInput :: String } | CBrace { pos :: Posn, remainingInput :: String } | AtVersion { pos :: Posn, remainingInput :: String } | AtAuthor { pos :: Posn, remainingInput :: String } | AtSee { pos :: Posn, remainingInput :: String, value :: String } | AtDoc { pos :: Posn, remainingInput :: String, value :: String } | BeginTag { pos :: Posn, remainingInput :: String, theTag :: Tag } | EndTag { pos :: Posn, remainingInput :: String, theTag :: Tag } | TagAttr { pos :: Posn, remainingInput :: String, attribute :: Attr } | TagAttrValue { pos :: Posn, remainingInput :: String, attrValue :: String } | TagAttrEq { pos :: Posn, remainingInput :: String } | SBr { pos :: Posn, remainingInput :: String } | SUnicode { pos :: Posn, remainingInput :: String, uniVal :: Unicode } | SText { pos :: Posn, remainingInput :: String, value :: String } | SWhiteSpace { pos :: Posn, remainingInput :: String } | ScanError String deriving Show data Tag = CodeTag | PreTag | EmTag | BoldTag | ParagraphTag | TTTag | ItalicsTag | StrongTag | AnchorTag deriving (Eq, Show) data Attr = HrefAttr | ClassAttr deriving (Eq, Show) data TagAttr = TaHref String | TaClass String deriving (Eq, Show) attrToTagAttr :: Attr -> String -> Either String TagAttr attrToTagAttr HrefAttr val = Right $ TaHref val attrToTagAttr ClassAttr val = Right $ TaClass val allAttrs :: [Attr] allAttrs = [HrefAttr, ClassAttr] attrNames :: [(String, Attr)] attrNames = [("href", HrefAttr), ("class", ClassAttr) ] tagAttrs :: [(Tag, [Attr])] tagAttrs = [(ParagraphTag, [ClassAttr]), (AnchorTag, [HrefAttr]) ] tagNames :: [(String, Tag)] tagNames = [("p", ParagraphTag), ("code", CodeTag), ("em", EmTag), ("b", BoldTag), ("tt", TTTag), ("i", ItalicsTag), ("strong", StrongTag), ("a", AnchorTag) ] nameOfTag :: Tag -> String nameOfTag t = case [n | (n,t') <- tagNames, t' == t] of [] -> error ("Oops: Tag `" ++ show t ++ "' doesn't have a name?\n\ \ This is a bug in HDoc, please report it.") (x:_) -> x com,hd,hd3,hd3Tag,hd3Ty,hdTag,hdTy,str :: Int com = 1 hd = 2 hd3 = 3 hd3Tag = 4 hd3Ty = 5 hdTag = 6 hdTy = 7 str = 8 hdoc_acts = [("arrow",arrow),("atauthor",atauthor),("atcons",atcons),("atdoc",atdoc),("atdoc3",atdoc3),("atmona",atmona),("atparam",atparam),("atret",atret),("atsee",atsee),("atsee3",atsee3),("atversion",atversion),("backToHd",backToHd),("blank",blank),("br",br),("cbrace",cbrace),("cbrack",cbrack),("comma",comma),("comment",comment),("comment2",comment2),("cparen",cparen),("docFollows",docFollows),("endHDocOld",endHDocOld),("endcomment",endcomment),("endhdoc3",endhdoc3),("endpre",endpre),("endstring",endstring),("extSym",extSym),("hdoc3",hdoc3),("hdoc3w",hdoc3w),("hdocCons1",hdocCons1),("hdocCons2",hdocCons2),("hdocOld",hdocOld),("hdocOldw",hdocOldw),("ht",ht),("ident",ident),("implies",implies),("name",name),("namedSymbol",namedSymbol),("newline",newline),("newline3",newline3),("newline3w",newline3w),("obrace",obrace),("obrack",obrack),("oparen",oparen),("pre",pre),("string",string),("tag",tag),("tagAttrName",tagAttrName),("tagAttrValue",tagAttrValue),("tagClose",tagClose),("tagEnd",tagEnd),("tagEq",tagEq),("text",text),("textOld",textOld),("textOldM",textOldM)] hdoc_lx :: [(Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)]))] hdoc_lx = [lx__0_0,lx__1_0,lx__2_0,lx__3_0,lx__4_0,lx__5_0,lx__6_0,lx__7_0,lx__8_0,lx__9_0,lx__10_0,lx__11_0,lx__12_0,lx__13_0,lx__14_0,lx__15_0,lx__16_0,lx__17_0,lx__18_0,lx__19_0,lx__20_0,lx__21_0,lx__22_0,lx__23_0,lx__24_0,lx__25_0,lx__26_0,lx__27_0,lx__28_0,lx__29_0,lx__30_0,lx__31_0,lx__32_0,lx__33_0,lx__34_0,lx__35_0,lx__36_0,lx__37_0,lx__38_0,lx__39_0,lx__40_0,lx__41_0,lx__42_0,lx__43_0,lx__44_0,lx__45_0,lx__46_0,lx__47_0,lx__48_0,lx__49_0,lx__50_0,lx__51_0,lx__52_0,lx__53_0,lx__54_0,lx__55_0,lx__56_0,lx__57_0,lx__58_0,lx__59_0,lx__60_0,lx__61_0,lx__62_0,lx__63_0,lx__64_0,lx__65_0,lx__66_0,lx__67_0,lx__68_0,lx__69_0,lx__70_0,lx__71_0,lx__72_0,lx__73_0,lx__74_0,lx__75_0,lx__76_0,lx__77_0,lx__78_0,lx__79_0,lx__80_0,lx__81_0,lx__82_0,lx__83_0,lx__84_0,lx__85_0,lx__86_0,lx__87_0,lx__88_0,lx__89_0,lx__90_0,lx__91_0,lx__92_0,lx__93_0,lx__94_0,lx__95_0,lx__96_0,lx__97_0,lx__98_0,lx__99_0,lx__100_0,lx__101_0,lx__102_0,lx__103_0,lx__104_0,lx__105_0,lx__106_0,lx__107_0,lx__108_0,lx__109_0,lx__110_0,lx__111_0,lx__112_0,lx__113_0,lx__114_0,lx__115_0,lx__116_0,lx__117_0,lx__118_0,lx__119_0,lx__120_0,lx__121_0,lx__122_0,lx__123_0,lx__124_0,lx__125_0,lx__126_0,lx__127_0,lx__128_0,lx__129_0,lx__130_0,lx__131_0,lx__132_0,lx__133_0,lx__134_0,lx__135_0,lx__136_0,lx__137_0,lx__138_0,lx__139_0,lx__140_0,lx__141_0,lx__142_0,lx__143_0,lx__144_0,lx__145_0,lx__146_0,lx__147_0,lx__148_0,lx__149_0,lx__150_0,lx__151_0,lx__152_0,lx__153_0,lx__154_0,lx__155_0,lx__156_0,lx__157_0,lx__158_0,lx__159_0,lx__160_0,lx__161_0,lx__162_0,lx__163_0,lx__164_0,lx__165_0,lx__166_0,lx__167_0,lx__168_0,lx__169_0,lx__170_0,lx__171_0,lx__172_0,lx__173_0,lx__174_0,lx__175_0,lx__176_0,lx__177_0,lx__178_0,lx__179_0,lx__180_0,lx__181_0,lx__182_0,lx__183_0,lx__184_0,lx__185_0,lx__186_0,lx__187_0,lx__188_0,lx__189_0,lx__190_0,lx__191_0,lx__192_0,lx__193_0,lx__194_0,lx__195_0,lx__196_0,lx__197_0,lx__198_0,lx__199_0,lx__200_0,lx__201_0,lx__202_0,lx__203_0,lx__204_0,lx__205_0,lx__206_0,lx__207_0,lx__208_0,lx__209_0,lx__210_0,lx__211_0,lx__212_0,lx__213_0,lx__214_0,lx__215_0,lx__216_0,lx__217_0,lx__218_0,lx__219_0,lx__220_0,lx__221_0,lx__222_0,lx__223_0,lx__224_0,lx__225_0,lx__226_0,lx__227_0,lx__228_0,lx__229_0,lx__230_0,lx__231_0,lx__232_0,lx__233_0,lx__234_0,lx__235_0,lx__236_0,lx__237_0,lx__238_0,lx__239_0,lx__240_0,lx__241_0,lx__242_0,lx__243_0,lx__244_0,lx__245_0,lx__246_0,lx__247_0,lx__248_0,lx__249_0,lx__250_0,lx__251_0,lx__252_0,lx__253_0,lx__254_0,lx__255_0,lx__256_0,lx__257_0,lx__258_0,lx__259_0,lx__260_0,lx__261_0,lx__262_0,lx__263_0,lx__264_0,lx__265_0,lx__266_0,lx__267_0,lx__268_0,lx__269_0,lx__270_0,lx__271_0] lx__0_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__0_0 = read "(False,[(70,\"backToHd\",[7,5],Nothing,Just 67)],62,(('\\t','~'),[('\\t',4),('\\n',17),('\\r',4),(' ',4),('!',59),('\"',2),('#',59),('$',59),('%',59),('&',64),('\\'',59),('(',10),(')',11),('*',59),('+',59),(',',9),('-',1),('.',59),('/',59),('0',59),('1',59),('2',59),('3',59),('4',59),('5',59),('6',59),('7',59),('8',59),('9',59),(':',8),(';',59),('<',15),('=',7),('>',16),('?',59),('@',63),('A',6),('B',6),('C',6),('D',6),('E',6),('F',6),('G',6),('H',6),('I',6),('J',6),('K',6),('L',6),('M',6),('N',6),('O',6),('P',6),('Q',6),('R',6),('S',6),('T',6),('U',6),('V',6),('W',6),('X',6),('Y',6),('Z',6),('[',12),('\\\\',61),(']',13),('_',60),('`',59),('a',5),('b',5),('c',5),('d',5),('e',5),('f',5),('g',5),('h',5),('i',5),('j',5),('k',5),('l',5),('m',5),('n',5),('o',5),('p',5),('q',5),('r',5),('s',5),('t',5),('u',5),('v',5),('w',5),('x',5),('y',5),('z',5),('{',3),('|',59),('}',14),('~',59)]))" lx__1_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__1_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(28,\"textOldM\",[2],Nothing,Just 116),(29,\"text\",[3],Nothing,Nothing),(69,\"docFollows\",[7,5],Nothing,Just 68)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',66),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('>',55),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',26),('~',121)]))" lx__2_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__2_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(3,\"string\",[0],Just (('\NUL','\\255'),[('\NUL',True),('\SOH',True),('\STX',True),('\ETX',True),('\EOT',True),('\ENQ',True),('\ACK',True),('\\a',True),('\\b',True),('\\t',True),('\\n',True),('\\v',True),('\\f',True),('\\r',True),('\SO',True),('\SI',True),('\DLE',True),('\DC1',True),('\DC2',True),('\DC3',True),('\DC4',True),('\NAK',True),('\SYN',True),('\ETB',True),('\CAN',True),('\EM',True),('\SUB',True),('\ESC',True),('\FS',True),('\GS',True),('\RS',True),('\US',True),(' ',True),('!',True),('\"',True),('#',True),('$',True),('%',True),('&',True),('\\'',True),('(',True),(')',True),('*',True),('+',True),(',',True),('-',True),('.',True),('/',True),('0',True),('1',True),('2',True),('3',True),('4',True),('5',True),('6',True),('7',True),('8',True),('9',True),(':',True),(';',True),('<',True),('=',True),('>',True),('?',True),('@',True),('A',True),('B',True),('C',True),('D',True),('E',True),('F',True),('G',True),('H',True),('I',True),('J',True),('K',True),('L',True),('M',True),('N',True),('O',True),('P',True),('Q',True),('R',True),('S',True),('T',True),('U',True),('V',True),('W',True),('X',True),('Y',True),('Z',True),('[',True),(']',True),('^',True),('_',True),('`',True),('a',True),('b',True),('c',True),('d',True),('e',True),('f',True),('g',True),('h',True),('i',True),('j',True),('k',True),('l',True),('m',True),('n',True),('o',True),('p',True),('q',True),('r',True),('s',True),('t',True),('u',True),('v',True),('w',True),('x',True),('y',True),('z',True),('{',True),('|',True),('}',True),('~',True),('\DEL',True),('\\128',True),('\\129',True),('\\130',True),('\\131',True),('\\132',True),('\\133',True),('\\134',True),('\\135',True),('\\136',True),('\\137',True),('\\138',True),('\\139',True),('\\140',True),('\\141',True),('\\142',True),('\\143',True),('\\144',True),('\\145',True),('\\146',True),('\\147',True),('\\148',True),('\\149',True),('\\150',True),('\\151',True),('\\152',True),('\\153',True),('\\154',True),('\\155',True),('\\156',True),('\\157',True),('\\158',True),('\\159',True),('\\160',True),('\\161',True),('\\162',True),('\\163',True),('\\164',True),('\\165',True),('\\166',True),('\\167',True),('\\168',True),('\\169',True),('\\170',True),('\\171',True),('\\172',True),('\\173',True),('\\174',True),('\\175',True),('\\176',True),('\\177',True),('\\178',True),('\\179',True),('\\180',True),('\\181',True),('\\182',True),('\\183',True),('\\184',True),('\\185',True),('\\186',True),('\\187',True),('\\188',True),('\\189',True),('\\190',True),('\\191',True),('\\192',True),('\\193',True),('\\194',True),('\\195',True),('\\196',True),('\\197',True),('\\198',True),('\\199',True),('\\200',True),('\\201',True),('\\202',True),('\\203',True),('\\204',True),('\\205',True),('\\206',True),('\\207',True),('\\208',True),('\\209',True),('\\210',True),('\\211',True),('\\212',True),('\\213',True),('\\214',True),('\\215',True),('\\216',True),('\\217',True),('\\218',True),('\\219',True),('\\220',True),('\\221',True),('\\222',True),('\\223',True),('\\224',True),('\\225',True),('\\226',True),('\\227',True),('\\228',True),('\\229',True),('\\230',True),('\\231',True),('\\232',True),('\\233',True),('\\234',True),('\\235',True),('\\236',True),('\\237',True),('\\238',True),('\\239',True),('\\240',True),('\\241',True),('\\242',True),('\\243',True),('\\244',True),('\\245',True),('\\246',True),('\\247',True),('\\248',True),('\\249',True),('\\250',True),('\\251',True),('\\252',True),('\\253',True),('\\254',True),('\\255',True)]),Nothing),(4,\"\",[8],Nothing,Nothing),(8,\"endstring\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(30,\"extSym\",[2,3],Nothing,Nothing)],110,(('\\n','\"'),[('\\n',-1),('\"',47)]))" lx__3_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__3_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(65,\"obrace\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',25),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__4_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__4_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(26,\"blank\",[2,3],Nothing,Nothing),(36,\"\",[6],Nothing,Nothing),(37,\"\",[4],Nothing,Nothing),(53,\"\",[7,5],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',36),('\\n',168),('\\r',36),(' ',36)]))" lx__5_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__5_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(38,\"tagAttrName\",[6,4],Nothing,Nothing),(67,\"ident\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',129),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',129),('1',129),('2',129),('3',129),('4',129),('5',129),('6',129),('7',129),('8',129),('9',129),(':',125),(';',125),('=',125),('?',125),('A',37),('B',37),('C',37),('D',37),('E',37),('F',37),('G',37),('H',37),('I',37),('J',37),('K',37),('L',37),('M',37),('N',37),('O',37),('P',37),('Q',37),('R',37),('S',37),('T',37),('U',37),('V',37),('W',37),('X',37),('Y',37),('Z',37),('[',125),('\\\\',125),(']',125),('_',129),('`',125),('a',37),('b',37),('c',37),('d',37),('e',37),('f',37),('g',37),('h',37),('i',37),('j',37),('k',37),('l',37),('m',37),('n',37),('o',37),('p',37),('q',37),('r',37),('s',37),('t',37),('u',37),('v',37),('w',37),('x',37),('y',37),('z',37),('{',125),('|',125),('}',121),('~',125)]))" lx__6_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__6_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(38,\"tagAttrName\",[6,4],Nothing,Nothing),(68,\"name\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',131),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',131),('1',131),('2',131),('3',131),('4',131),('5',131),('6',131),('7',131),('8',131),('9',131),(':',125),(';',125),('=',125),('?',125),('A',38),('B',38),('C',38),('D',38),('E',38),('F',38),('G',38),('H',38),('I',38),('J',38),('K',38),('L',38),('M',38),('N',38),('O',38),('P',38),('Q',38),('R',38),('S',38),('T',38),('U',38),('V',38),('W',38),('X',38),('Y',38),('Z',38),('[',125),('\\\\',125),(']',125),('_',131),('`',125),('a',38),('b',38),('c',38),('d',38),('e',38),('f',38),('g',38),('h',38),('i',38),('j',38),('k',38),('l',38),('m',38),('n',38),('o',38),('p',38),('q',38),('r',38),('s',38),('t',38),('u',38),('v',38),('w',38),('x',38),('y',38),('z',38),('{',125),('|',125),('}',121),('~',125)]))" lx__7_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__7_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(39,\"tagEq\",[6,4],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('>',56),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__8_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__8_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(68,\"name\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',130),('%',125),('\\'',125),('(',125),(')',125),('*',130),('+',130),(',',125),('-',41),('.',125),('/',130),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',39),(';',125),('<',58),('=',130),('>',58),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',130),('}',121),('~',130)]))" lx__9_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__9_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(60,\"comma\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__10_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__10_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(61,\"oparen\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',126),('%',125),('\\'',125),('(',125),(')',125),('*',126),('+',126),(',',125),('-',123),('.',260),('/',126),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('<',166),('=',126),('>',166),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',126),('}',121),('~',126)]))" lx__11_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__11_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(62,\"cparen\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__12_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__12_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(63,\"obrack\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__13_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__13_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(64,\"cbrack\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__14_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__14_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(66,\"cbrace\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__15_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__15_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(30,\"extSym\",[2,3],Nothing,Nothing)],-1,(('/','z'),[('/',114),('A',270),('B',263),('C',270),('D',270),('E',270),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',271),('Q',270),('R',270),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',263),('c',270),('d',270),('e',270),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',271),('q',270),('r',270),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))" lx__16_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__16_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(30,\"extSym\",[2,3],Nothing,Nothing),(41,\"tagClose\",[6,4],Nothing,Nothing)],-1,(('0','0'),[]))" lx__17_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__17_0 = read "(False,[(1,\"\",[0],Nothing,Nothing),(13,\"\",[1],Nothing,Nothing),(18,\"newline\",[2],Nothing,Nothing),(23,\"endhdoc3\",[3,5],Nothing,Just 258),(36,\"\",[6],Nothing,Nothing),(54,\"\",[7],Nothing,Nothing)],-1,(('\\t','-'),[('\\t',33),('\\r',33),(' ',33),('-',117)]))" lx__18_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__18_0 = read "(False,[(21,\"hdoc3\",[0],Nothing,Just 70),(28,\"textOldM\",[2],Nothing,Just 116),(29,\"text\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',32),('\\n',167),('\\r',32),(' ',32),('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',65),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__19_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__19_0 = read "(False,[(2,\"\",[0],Nothing,Nothing),(28,\"textOldM\",[2],Nothing,Just 116),(29,\"text\",[3],Nothing,Nothing)],21,(('\\n','~'),[('\\n',-1),('!',20),('#',20),('$',20),('%',20),('\\'',20),('(',20),(')',20),('*',20),('+',20),(',',20),('-',19),('.',20),('/',20),('0',20),('1',20),('2',20),('3',20),('4',20),('5',20),('6',20),('7',20),('8',20),('9',20),(':',20),(';',20),('=',20),('?',20),('A',20),('B',20),('C',20),('D',20),('E',20),('F',20),('G',20),('H',20),('I',20),('J',20),('K',20),('L',20),('M',20),('N',20),('O',20),('P',20),('Q',20),('R',20),('S',20),('T',20),('U',20),('V',20),('W',20),('X',20),('Y',20),('Z',20),('[',20),('\\\\',20),(']',20),('_',20),('`',20),('a',20),('b',20),('c',20),('d',20),('e',20),('f',20),('g',20),('h',20),('i',20),('j',20),('k',20),('l',20),('m',20),('n',20),('o',20),('p',20),('q',20),('r',20),('s',20),('t',20),('u',20),('v',20),('w',20),('x',20),('y',20),('z',20),('{',20),('|',20),('}',20),('~',20)]))" lx__20_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__20_0 = read "(False,[(2,\"\",[0],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],21,(('\\n','~'),[('\\n',-1),('!',20),('#',20),('$',20),('%',20),('\\'',20),('(',20),(')',20),('*',20),('+',20),(',',20),('-',20),('.',20),('/',20),('0',20),('1',20),('2',20),('3',20),('4',20),('5',20),('6',20),('7',20),('8',20),('9',20),(':',20),(';',20),('=',20),('?',20),('A',20),('B',20),('C',20),('D',20),('E',20),('F',20),('G',20),('H',20),('I',20),('J',20),('K',20),('L',20),('M',20),('N',20),('O',20),('P',20),('Q',20),('R',20),('S',20),('T',20),('U',20),('V',20),('W',20),('X',20),('Y',20),('Z',20),('[',20),('\\\\',20),(']',20),('_',20),('`',20),('a',20),('b',20),('c',20),('d',20),('e',20),('f',20),('g',20),('h',20),('i',20),('j',20),('k',20),('l',20),('m',20),('n',20),('o',20),('p',20),('q',20),('r',20),('s',20),('t',20),('u',20),('v',20),('w',20),('x',20),('y',20),('z',20),('{',20),('|',20),('}',20),('~',20)]))" lx__21_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__21_0 = read "(False,[(2,\"\",[0],Nothing,Nothing)],21,(('\\n','\\n'),[('\\n',-1)]))" lx__22_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__22_0 = read "(False,[(5,\"\",[8],Nothing,Nothing)],-1,(('0','0'),[]))" lx__23_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__23_0 = read "(False,[(6,\"\",[8],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__24_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__24_0 = read "(False,[(7,\"\",[8],Nothing,Nothing)],-1,(('0','0'),[]))" lx__25_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__25_0 = read "(False,[(9,\"comment\",[0],Nothing,Nothing),(10,\"comment2\",[1],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',124),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__26_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__26_0 = read "(False,[(11,\"endcomment\",[1],Nothing,Nothing),(17,\"endHDocOld\",[2,7],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__27_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__27_0 = read "(False,[(14,\"\",[0],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__28_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__28_0 = read "(False,[(15,\"hdocOld\",[0],Nothing,Just 70),(29,\"text\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',30),('\\n',30),('\\v',30),('\\f',30),('\\r',30),(' ',30),('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__29_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__29_0 = read "(True,[(0,\"\",[],Nothing,Nothing)],-1,(('0','0'),[]))" lx__30_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__30_0 = read "(False,[(16,\"hdocOldw\",[0],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',30),('\\n',30),('\\v',30),('\\f',30),('\\r',30),(' ',30)]))" lx__31_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__31_0 = read "(False,[(19,\"hdocCons1\",[0],Nothing,Just 100),(20,\"hdocCons2\",[0],Nothing,Just 70),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__32_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__32_0 = read "(False,[(22,\"hdoc3w\",[0],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',32),('\\n',167),('\\r',32),(' ',32)]))" lx__33_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__33_0 = read "(False,[(23,\"endhdoc3\",[3,5],Nothing,Just 258)],-1,(('\\t','-'),[('\\t',33),('\\r',33),(' ',33),('-',117)]))" lx__34_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__34_0 = read "(False,[(24,\"newline3\",[3],Nothing,Just 70),(37,\"\",[4],Nothing,Nothing),(56,\"\",[5],Nothing,Just 70)],-1,(('\\t',' '),[('\\t',35),('\\n',168),('\\r',35),(' ',35)]))" lx__35_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__35_0 = read "(False,[(25,\"newline3w\",[3],Nothing,Nothing),(37,\"\",[4],Nothing,Nothing),(55,\"\",[5],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',35),('\\n',168),('\\r',35),(' ',35)]))" lx__36_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__36_0 = read "(False,[(26,\"blank\",[2,3],Nothing,Nothing),(37,\"\",[4],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',36),('\\n',168),('\\r',36),(' ',36)]))" lx__37_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__37_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(38,\"tagAttrName\",[6,4],Nothing,Nothing),(67,\"ident\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',129),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',129),('1',129),('2',129),('3',129),('4',129),('5',129),('6',129),('7',129),('8',129),('9',129),(':',125),(';',125),('=',125),('?',125),('A',37),('B',37),('C',37),('D',37),('E',37),('F',37),('G',37),('H',37),('I',37),('J',37),('K',37),('L',37),('M',37),('N',37),('O',37),('P',37),('Q',37),('R',37),('S',37),('T',37),('U',37),('V',37),('W',37),('X',37),('Y',37),('Z',37),('[',125),('\\\\',125),(']',125),('_',129),('`',125),('a',37),('b',37),('c',37),('d',37),('e',37),('f',37),('g',37),('h',37),('i',37),('j',37),('k',37),('l',37),('m',37),('n',37),('o',37),('p',37),('q',37),('r',37),('s',37),('t',37),('u',37),('v',37),('w',37),('x',37),('y',37),('z',37),('{',125),('|',125),('}',121),('~',125)]))" lx__38_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__38_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(38,\"tagAttrName\",[6,4],Nothing,Nothing),(68,\"name\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',131),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',131),('1',131),('2',131),('3',131),('4',131),('5',131),('6',131),('7',131),('8',131),('9',131),(':',125),(';',125),('=',125),('?',125),('A',38),('B',38),('C',38),('D',38),('E',38),('F',38),('G',38),('H',38),('I',38),('J',38),('K',38),('L',38),('M',38),('N',38),('O',38),('P',38),('Q',38),('R',38),('S',38),('T',38),('U',38),('V',38),('W',38),('X',38),('Y',38),('Z',38),('[',125),('\\\\',125),(']',125),('_',131),('`',125),('a',38),('b',38),('c',38),('d',38),('e',38),('f',38),('g',38),('h',38),('i',38),('j',38),('k',38),('l',38),('m',38),('n',38),('o',38),('p',38),('q',38),('r',38),('s',38),('t',38),('u',38),('v',38),('w',38),('x',38),('y',38),('z',38),('{',125),('|',125),('}',121),('~',125)]))" lx__39_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__39_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(59,\"ht\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',130),('%',125),('\\'',125),('(',125),(')',125),('*',130),('+',130),(',',125),('-',41),('.',125),('/',130),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',130),(';',125),('<',58),('=',130),('>',58),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',130),('}',121),('~',130)]))" lx__40_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__40_0 = read "(False,[(29,\"text\",[3],Nothing,Nothing),(67,\"ident\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__41_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__41_0 = read "(False,[(29,\"text\",[3],Nothing,Nothing),(68,\"name\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',41),('%',121),('\\'',121),('(',121),(')',121),('*',41),('+',41),(',',121),('-',41),('.',121),('/',41),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',41),(';',121),('<',58),('=',41),('>',58),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',41),('}',121),('~',41)]))" lx__42_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__42_0 = read "(False,[(31,\"namedSymbol\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__43_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__43_0 = read "(False,[(32,\"pre\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__44_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__44_0 = read "(False,[(33,\"endpre\",[2,3],Nothing,Nothing),(42,\"tagEnd\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__45_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__45_0 = read "(False,[(34,\"br\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__46_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__46_0 = read "(False,[(37,\"\",[4],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',46),('\\n',168),('\\r',46),(' ',46)]))" lx__47_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__47_0 = read "(False,[(40,\"tagAttrValue\",[6,4],Nothing,Nothing)],-1,(('0','0'),[]))" lx__48_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__48_0 = read "(False,[(42,\"tagEnd\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__49_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__49_0 = read "(False,[(43,\"atcons\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__50_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__50_0 = read "(False,[(44,\"atparam\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__51_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__51_0 = read "(False,[(45,\"atret\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__52_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__52_0 = read "(False,[(46,\"atmona\",[2,3],Nothing,Nothing)],-1,(('0','0'),[]))" lx__53_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__53_0 = read "(False,[(47,\"atauthor\",[2,3],Nothing,Just 100)],-1,(('0','0'),[]))" lx__54_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__54_0 = read "(False,[(48,\"atversion\",[2,3],Nothing,Just 100)],-1,(('0','0'),[]))" lx__55_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__55_0 = read "(False,[(57,\"arrow\",[7,5],Nothing,Nothing)],-1,(('0','0'),[]))" lx__56_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__56_0 = read "(False,[(58,\"implies\",[7,5],Nothing,Nothing)],-1,(('0','0'),[]))" lx__57_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__57_0 = read "(False,[(67,\"ident\",[7,5],Nothing,Nothing)],-1,(('0','0'),[]))" lx__58_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__58_0 = read "(False,[(68,\"name\",[7,5],Nothing,Nothing)],-1,(('$','~'),[('$',58),('*',58),('+',58),('-',58),('/',58),(':',58),('<',58),('=',58),('>',58),('|',58),('~',58)]))" lx__59_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__59_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__60_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__60_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',129),('1',129),('2',129),('3',129),('4',129),('5',129),('6',129),('7',129),('8',129),('9',129),(':',125),(';',125),('=',125),('?',125),('A',131),('B',131),('C',131),('D',131),('E',131),('F',131),('G',131),('H',131),('I',131),('J',131),('K',131),('L',131),('M',131),('N',131),('O',131),('P',131),('Q',131),('R',131),('S',131),('T',131),('U',131),('V',131),('W',131),('X',131),('Y',131),('Z',131),('[',125),('\\\\',125),(']',125),('_',127),('`',125),('a',129),('b',129),('c',129),('d',129),('e',129),('f',129),('g',129),('h',129),('i',129),('j',129),('k',129),('l',129),('m',129),('n',129),('o',129),('p',129),('q',129),('r',129),('s',129),('t',129),('u',129),('v',129),('w',129),('x',129),('y',129),('z',129),('{',125),('|',125),('}',121),('~',125)]))" lx__61_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__61_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing),(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',221),('\\n',120),('\\v',221),('\\f',221),('\\r',221),(' ',221),('!',125),('\"',24),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',23),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__62_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__62_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing)],-1,(('0','0'),[]))" lx__63_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__63_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing)],-1,(('a','v'),[('a',251),('c',267),('d',226),('m',266),('p',252),('r',239),('s',241),('v',240)]))" lx__64_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__64_0 = read "(False,[(0,\"\",[0],Nothing,Nothing),(4,\"\",[8],Nothing,Nothing),(12,\"\",[1],Nothing,Nothing)],-1,((';','z'),[(';',42),('A',115),('B',115),('C',115),('D',115),('E',115),('F',115),('G',115),('H',115),('I',115),('J',115),('K',115),('L',115),('M',115),('N',115),('O',115),('P',115),('Q',115),('R',115),('S',115),('T',115),('U',115),('V',115),('W',115),('X',115),('Y',115),('Z',115),('a',115),('b',115),('c',115),('d',115),('e',115),('f',115),('g',115),('h',115),('i',115),('j',115),('k',115),('l',115),('m',115),('n',115),('o',115),('p',115),('q',115),('r',115),('s',115),('t',115),('u',115),('v',115),('w',115),('x',115),('y',115),('z',115)]))" lx__65_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__65_0 = read "(False,[(28,\"textOldM\",[2],Nothing,Just 116),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',19),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__66_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__66_0 = read "(False,[(28,\"textOldM\",[2],Nothing,Just 116),(29,\"text\",[3],Nothing,Nothing)],21,(('!','~'),[('!',20),('#',20),('$',20),('%',20),('\\'',31),('(',20),(')',20),('*',20),('+',20),(',',20),('-',18),('.',20),('/',20),('0',20),('1',20),('2',20),('3',20),('4',20),('5',20),('6',20),('7',20),('8',20),('9',20),(':',20),(';',20),('=',20),('?',20),('A',20),('B',20),('C',20),('D',20),('E',20),('F',20),('G',20),('H',20),('I',20),('J',20),('K',20),('L',20),('M',20),('N',20),('O',20),('P',20),('Q',20),('R',20),('S',20),('T',20),('U',20),('V',20),('W',20),('X',20),('Y',20),('Z',20),('[',20),('\\\\',20),(']',20),('_',20),('`',20),('a',20),('b',20),('c',20),('d',20),('e',20),('f',20),('g',20),('h',20),('i',20),('j',20),('k',20),('l',20),('m',20),('n',20),('o',20),('p',20),('q',20),('r',20),('s',20),('t',20),('u',20),('v',20),('w',20),('x',20),('y',20),('z',20),('{',20),('|',20),('}',20),('~',20)]))" lx__67_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__67_0 = read "(False,[],-1,(('@','@'),[('@',29)]))" lx__68_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__68_0 = read "(False,[],29,(('>','}'),[('>',-1),('}',-1)]))" lx__69_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__69_0 = read "(False,[],-1,(('$','~'),[('$',69),(')',57),('*',69),('+',69),('-',69),('.',69),('/',69),('<',69),('=',69),('>',69),('|',69),('~',69)]))" lx__70_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__70_0 = read "(False,[],29,(('-','-'),[('-',-1)]))" lx__71_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__71_0 = read "(False,[],-1,(('-','-'),[('-',156)]))" lx__72_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__72_0 = read "(False,[],-1,(('\\'','z'),[('\\'',72),(')',156),('0',72),('1',72),('2',72),('3',72),('4',72),('5',72),('6',72),('7',72),('8',72),('9',72),('A',72),('B',72),('C',72),('D',72),('E',72),('F',72),('G',72),('H',72),('I',72),('J',72),('K',72),('L',72),('M',72),('N',72),('O',72),('P',72),('Q',72),('R',72),('S',72),('T',72),('U',72),('V',72),('W',72),('X',72),('Y',72),('Z',72),('_',72),('a',72),('b',72),('c',72),('d',72),('e',72),('f',72),('g',72),('h',72),('i',72),('j',72),('k',72),('l',72),('m',72),('n',72),('o',72),('p',72),('q',72),('r',72),('s',72),('t',72),('u',72),('v',72),('w',72),('x',72),('y',72),('z',72)]))" lx__73_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__73_0 = read "(False,[],-1,(('$','~'),[('$',157),('*',157),('+',157),('-',157),('/',157),(':',157),('<',157),('=',157),('>',157),('|',157),('~',157)]))" lx__74_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__74_0 = read "(False,[],-1,(('0','z'),[('0',159),('1',159),('2',159),('3',159),('4',159),('5',159),('6',159),('7',159),('8',159),('9',159),('A',159),('B',159),('C',159),('D',159),('E',159),('F',159),('G',159),('H',159),('I',159),('J',159),('K',159),('L',159),('M',159),('N',159),('O',159),('P',159),('Q',159),('R',159),('S',159),('T',159),('U',159),('V',159),('W',159),('X',159),('Y',159),('Z',159),('_',74),('a',159),('b',159),('c',159),('d',159),('e',159),('f',159),('g',159),('h',159),('i',159),('j',159),('k',159),('l',159),('m',159),('n',159),('o',159),('p',159),('q',159),('r',159),('s',159),('t',159),('u',159),('v',159),('w',159),('x',159),('y',159),('z',159)]))" lx__75_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__75_0 = read "(False,[],-1,(('\\t','z'),[('\\t',75),('\\n',264),('\\r',75),(' ',75),('(',210),(':',158),('A',159),('B',159),('C',159),('D',159),('E',159),('F',159),('G',159),('H',159),('I',159),('J',159),('K',159),('L',159),('M',159),('N',159),('O',159),('P',159),('Q',159),('R',159),('S',159),('T',159),('U',159),('V',159),('W',159),('X',159),('Y',159),('Z',159),('_',74),('a',159),('b',159),('c',159),('d',159),('e',159),('f',159),('g',159),('h',159),('i',159),('j',159),('k',159),('l',159),('m',159),('n',159),('o',159),('p',159),('q',159),('r',159),('s',159),('t',159),('u',159),('v',159),('w',159),('x',159),('y',159),('z',159)]))" lx__76_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__76_0 = read "(False,[],-1,(('\\'','z'),[('\\'',76),(')',147),('0',76),('1',76),('2',76),('3',76),('4',76),('5',76),('6',76),('7',76),('8',76),('9',76),('A',76),('B',76),('C',76),('D',76),('E',76),('F',76),('G',76),('H',76),('I',76),('J',76),('K',76),('L',76),('M',76),('N',76),('O',76),('P',76),('Q',76),('R',76),('S',76),('T',76),('U',76),('V',76),('W',76),('X',76),('Y',76),('Z',76),('_',76),('a',76),('b',76),('c',76),('d',76),('e',76),('f',76),('g',76),('h',76),('i',76),('j',76),('k',76),('l',76),('m',76),('n',76),('o',76),('p',76),('q',76),('r',76),('s',76),('t',76),('u',76),('v',76),('w',76),('x',76),('y',76),('z',76)]))" lx__77_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__77_0 = read "(False,[],-1,(('\\'','z'),[('\\'',77),(')',151),('0',77),('1',77),('2',77),('3',77),('4',77),('5',77),('6',77),('7',77),('8',77),('9',77),('A',77),('B',77),('C',77),('D',77),('E',77),('F',77),('G',77),('H',77),('I',77),('J',77),('K',77),('L',77),('M',77),('N',77),('O',77),('P',77),('Q',77),('R',77),('S',77),('T',77),('U',77),('V',77),('W',77),('X',77),('Y',77),('Z',77),('_',77),('a',77),('b',77),('c',77),('d',77),('e',77),('f',77),('g',77),('h',77),('i',77),('j',77),('k',77),('l',77),('m',77),('n',77),('o',77),('p',77),('q',77),('r',77),('s',77),('t',77),('u',77),('v',77),('w',77),('x',77),('y',77),('z',77)]))" lx__78_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__78_0 = read "(False,[],-1,(('$','~'),[('$',148),('*',148),('+',148),('-',148),('/',148),(':',148),('<',148),('=',148),('>',148),('|',148),('~',148)]))" lx__79_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__79_0 = read "(False,[],-1,(('$','~'),[('$',153),('*',153),('+',153),('-',153),('/',153),(':',153),('<',153),('=',153),('>',153),('|',153),('~',153)]))" lx__80_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__80_0 = read "(False,[],-1,(('0','z'),[('0',150),('1',150),('2',150),('3',150),('4',150),('5',150),('6',150),('7',150),('8',150),('9',150),('A',150),('B',150),('C',150),('D',150),('E',150),('F',150),('G',150),('H',150),('I',150),('J',150),('K',150),('L',150),('M',150),('N',150),('O',150),('P',150),('Q',150),('R',150),('S',150),('T',150),('U',150),('V',150),('W',150),('X',150),('Y',150),('Z',150),('_',80),('a',150),('b',150),('c',150),('d',150),('e',150),('f',150),('g',150),('h',150),('i',150),('j',150),('k',150),('l',150),('m',150),('n',150),('o',150),('p',150),('q',150),('r',150),('s',150),('t',150),('u',150),('v',150),('w',150),('x',150),('y',150),('z',150)]))" lx__81_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__81_0 = read "(False,[],-1,(('0','z'),[('0',155),('1',155),('2',155),('3',155),('4',155),('5',155),('6',155),('7',155),('8',155),('9',155),('A',155),('B',155),('C',155),('D',155),('E',155),('F',155),('G',155),('H',155),('I',155),('J',155),('K',155),('L',155),('M',155),('N',155),('O',155),('P',155),('Q',155),('R',155),('S',155),('T',155),('U',155),('V',155),('W',155),('X',155),('Y',155),('Z',155),('_',81),('a',155),('b',155),('c',155),('d',155),('e',155),('f',155),('g',155),('h',155),('i',155),('j',155),('k',155),('l',155),('m',155),('n',155),('o',155),('p',155),('q',155),('r',155),('s',155),('t',155),('u',155),('v',155),('w',155),('x',155),('y',155),('z',155)]))" lx__82_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__82_0 = read "(False,[],-1,(('\\t','z'),[('\\t',82),('\\n',84),('\\v',84),('\\f',84),('\\r',82),(' ',82),('(',208),('-',212),(':',154),('A',155),('B',155),('C',155),('D',155),('E',155),('F',155),('G',155),('H',155),('I',155),('J',155),('K',155),('L',155),('M',155),('N',155),('O',155),('P',155),('Q',155),('R',155),('S',155),('T',155),('U',155),('V',155),('W',155),('X',155),('Y',155),('Z',155),('_',81),('a',155),('b',155),('c',155),('d',155),('e',155),('f',155),('g',155),('h',155),('i',155),('j',155),('k',155),('l',155),('m',155),('n',155),('o',155),('p',155),('q',155),('r',155),('s',155),('t',155),('u',155),('v',155),('w',155),('x',155),('y',155),('z',155)]))" lx__83_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__83_0 = read "(False,[],-1,(('\\t','z'),[('\\t',83),('\\n',82),('\\v',84),('\\f',84),('\\r',83),(' ',83),('(',209),(':',149),('A',150),('B',150),('C',150),('D',150),('E',150),('F',150),('G',150),('H',150),('I',150),('J',150),('K',150),('L',150),('M',150),('N',150),('O',150),('P',150),('Q',150),('R',150),('S',150),('T',150),('U',150),('V',150),('W',150),('X',150),('Y',150),('Z',150),('_',80),('a',150),('b',150),('c',150),('d',150),('e',150),('f',150),('g',150),('h',150),('i',150),('j',150),('k',150),('l',150),('m',150),('n',150),('o',150),('p',150),('q',150),('r',150),('s',150),('t',150),('u',150),('v',150),('w',150),('x',150),('y',150),('z',150)]))" lx__84_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__84_0 = read "(False,[],-1,(('\\t','z'),[('\\t',84),('\\n',84),('\\v',84),('\\f',84),('\\r',84),(' ',84),('(',208),(':',154),('A',155),('B',155),('C',155),('D',155),('E',155),('F',155),('G',155),('H',155),('I',155),('J',155),('K',155),('L',155),('M',155),('N',155),('O',155),('P',155),('Q',155),('R',155),('S',155),('T',155),('U',155),('V',155),('W',155),('X',155),('Y',155),('Z',155),('_',81),('a',155),('b',155),('c',155),('d',155),('e',155),('f',155),('g',155),('h',155),('i',155),('j',155),('k',155),('l',155),('m',155),('n',155),('o',155),('p',155),('q',155),('r',155),('s',155),('t',155),('u',155),('v',155),('w',155),('x',155),('y',155),('z',155)]))" lx__85_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__85_0 = read "(False,[],-1,(('c','c'),[('c',223)]))" lx__86_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__86_0 = read "(False,[],-1,(('-','-'),[('-',143)]))" lx__87_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__87_0 = read "(False,[],-1,(('\\'','z'),[('\\'',87),(')',143),('0',87),('1',87),('2',87),('3',87),('4',87),('5',87),('6',87),('7',87),('8',87),('9',87),('A',87),('B',87),('C',87),('D',87),('E',87),('F',87),('G',87),('H',87),('I',87),('J',87),('K',87),('L',87),('M',87),('N',87),('O',87),('P',87),('Q',87),('R',87),('S',87),('T',87),('U',87),('V',87),('W',87),('X',87),('Y',87),('Z',87),('_',87),('a',87),('b',87),('c',87),('d',87),('e',87),('f',87),('g',87),('h',87),('i',87),('j',87),('k',87),('l',87),('m',87),('n',87),('o',87),('p',87),('q',87),('r',87),('s',87),('t',87),('u',87),('v',87),('w',87),('x',87),('y',87),('z',87)]))" lx__88_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__88_0 = read "(False,[],-1,(('$','~'),[('$',144),('*',144),('+',144),('-',144),('/',144),(':',144),('<',144),('=',144),('>',144),('|',144),('~',144)]))" lx__89_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__89_0 = read "(False,[],-1,(('0','z'),[('0',146),('1',146),('2',146),('3',146),('4',146),('5',146),('6',146),('7',146),('8',146),('9',146),('A',146),('B',146),('C',146),('D',146),('E',146),('F',146),('G',146),('H',146),('I',146),('J',146),('K',146),('L',146),('M',146),('N',146),('O',146),('P',146),('Q',146),('R',146),('S',146),('T',146),('U',146),('V',146),('W',146),('X',146),('Y',146),('Z',146),('_',89),('a',146),('b',146),('c',146),('d',146),('e',146),('f',146),('g',146),('h',146),('i',146),('j',146),('k',146),('l',146),('m',146),('n',146),('o',146),('p',146),('q',146),('r',146),('s',146),('t',146),('u',146),('v',146),('w',146),('x',146),('y',146),('z',146)]))" lx__90_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__90_0 = read "(False,[],-1,(('\\t','z'),[('\\t',90),('\\n',265),('\\r',90),(' ',90),('(',207),(':',145),('A',146),('B',146),('C',146),('D',146),('E',146),('F',146),('G',146),('H',146),('I',146),('J',146),('K',146),('L',146),('M',146),('N',146),('O',146),('P',146),('Q',146),('R',146),('S',146),('T',146),('U',146),('V',146),('W',146),('X',146),('Y',146),('Z',146),('_',89),('a',146),('b',146),('c',146),('d',146),('e',146),('f',146),('g',146),('h',146),('i',146),('j',146),('k',146),('l',146),('m',146),('n',146),('o',146),('p',146),('q',146),('r',146),('s',146),('t',146),('u',146),('v',146),('w',146),('x',146),('y',146),('z',146)]))" lx__91_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__91_0 = read "(False,[],-1,(('\\'','z'),[('\\'',91),(')',134),('0',91),('1',91),('2',91),('3',91),('4',91),('5',91),('6',91),('7',91),('8',91),('9',91),('A',91),('B',91),('C',91),('D',91),('E',91),('F',91),('G',91),('H',91),('I',91),('J',91),('K',91),('L',91),('M',91),('N',91),('O',91),('P',91),('Q',91),('R',91),('S',91),('T',91),('U',91),('V',91),('W',91),('X',91),('Y',91),('Z',91),('_',91),('a',91),('b',91),('c',91),('d',91),('e',91),('f',91),('g',91),('h',91),('i',91),('j',91),('k',91),('l',91),('m',91),('n',91),('o',91),('p',91),('q',91),('r',91),('s',91),('t',91),('u',91),('v',91),('w',91),('x',91),('y',91),('z',91)]))" lx__92_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__92_0 = read "(False,[],-1,(('\\'','z'),[('\\'',92),(')',138),('0',92),('1',92),('2',92),('3',92),('4',92),('5',92),('6',92),('7',92),('8',92),('9',92),('A',92),('B',92),('C',92),('D',92),('E',92),('F',92),('G',92),('H',92),('I',92),('J',92),('K',92),('L',92),('M',92),('N',92),('O',92),('P',92),('Q',92),('R',92),('S',92),('T',92),('U',92),('V',92),('W',92),('X',92),('Y',92),('Z',92),('_',92),('a',92),('b',92),('c',92),('d',92),('e',92),('f',92),('g',92),('h',92),('i',92),('j',92),('k',92),('l',92),('m',92),('n',92),('o',92),('p',92),('q',92),('r',92),('s',92),('t',92),('u',92),('v',92),('w',92),('x',92),('y',92),('z',92)]))" lx__93_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__93_0 = read "(False,[],-1,(('$','~'),[('$',135),('*',135),('+',135),('-',135),('/',135),(':',135),('<',135),('=',135),('>',135),('|',135),('~',135)]))" lx__94_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__94_0 = read "(False,[],-1,(('$','~'),[('$',140),('*',140),('+',140),('-',140),('/',140),(':',140),('<',140),('=',140),('>',140),('|',140),('~',140)]))" lx__95_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__95_0 = read "(False,[],-1,(('0','z'),[('0',137),('1',137),('2',137),('3',137),('4',137),('5',137),('6',137),('7',137),('8',137),('9',137),('A',137),('B',137),('C',137),('D',137),('E',137),('F',137),('G',137),('H',137),('I',137),('J',137),('K',137),('L',137),('M',137),('N',137),('O',137),('P',137),('Q',137),('R',137),('S',137),('T',137),('U',137),('V',137),('W',137),('X',137),('Y',137),('Z',137),('_',95),('a',137),('b',137),('c',137),('d',137),('e',137),('f',137),('g',137),('h',137),('i',137),('j',137),('k',137),('l',137),('m',137),('n',137),('o',137),('p',137),('q',137),('r',137),('s',137),('t',137),('u',137),('v',137),('w',137),('x',137),('y',137),('z',137)]))" lx__96_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__96_0 = read "(False,[],-1,(('0','z'),[('0',142),('1',142),('2',142),('3',142),('4',142),('5',142),('6',142),('7',142),('8',142),('9',142),('A',142),('B',142),('C',142),('D',142),('E',142),('F',142),('G',142),('H',142),('I',142),('J',142),('K',142),('L',142),('M',142),('N',142),('O',142),('P',142),('Q',142),('R',142),('S',142),('T',142),('U',142),('V',142),('W',142),('X',142),('Y',142),('Z',142),('_',96),('a',142),('b',142),('c',142),('d',142),('e',142),('f',142),('g',142),('h',142),('i',142),('j',142),('k',142),('l',142),('m',142),('n',142),('o',142),('p',142),('q',142),('r',142),('s',142),('t',142),('u',142),('v',142),('w',142),('x',142),('y',142),('z',142)]))" lx__97_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__97_0 = read "(False,[],-1,(('\\t','z'),[('\\t',97),('\\n',99),('\\v',99),('\\f',99),('\\r',97),(' ',97),('(',205),('-',211),(':',141),('A',142),('B',142),('C',142),('D',142),('E',142),('F',142),('G',142),('H',142),('I',142),('J',142),('K',142),('L',142),('M',142),('N',142),('O',142),('P',142),('Q',142),('R',142),('S',142),('T',142),('U',142),('V',142),('W',142),('X',142),('Y',142),('Z',142),('_',96),('a',142),('b',142),('c',142),('d',142),('e',142),('f',142),('g',142),('h',142),('i',142),('j',142),('k',142),('l',142),('m',142),('n',142),('o',142),('p',142),('q',142),('r',142),('s',142),('t',142),('u',142),('v',142),('w',142),('x',142),('y',142),('z',142)]))" lx__98_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__98_0 = read "(False,[],-1,(('\\t','z'),[('\\t',98),('\\n',97),('\\v',99),('\\f',99),('\\r',98),(' ',98),('(',206),(':',136),('A',137),('B',137),('C',137),('D',137),('E',137),('F',137),('G',137),('H',137),('I',137),('J',137),('K',137),('L',137),('M',137),('N',137),('O',137),('P',137),('Q',137),('R',137),('S',137),('T',137),('U',137),('V',137),('W',137),('X',137),('Y',137),('Z',137),('_',95),('a',137),('b',137),('c',137),('d',137),('e',137),('f',137),('g',137),('h',137),('i',137),('j',137),('k',137),('l',137),('m',137),('n',137),('o',137),('p',137),('q',137),('r',137),('s',137),('t',137),('u',137),('v',137),('w',137),('x',137),('y',137),('z',137)]))" lx__99_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__99_0 = read "(False,[],-1,(('\\t','z'),[('\\t',99),('\\n',99),('\\v',99),('\\f',99),('\\r',99),(' ',99),('(',205),(':',141),('A',142),('B',142),('C',142),('D',142),('E',142),('F',142),('G',142),('H',142),('I',142),('J',142),('K',142),('L',142),('M',142),('N',142),('O',142),('P',142),('Q',142),('R',142),('S',142),('T',142),('U',142),('V',142),('W',142),('X',142),('Y',142),('Z',142),('_',96),('a',142),('b',142),('c',142),('d',142),('e',142),('f',142),('g',142),('h',142),('i',142),('j',142),('k',142),('l',142),('m',142),('n',142),('o',142),('p',142),('q',142),('r',142),('s',142),('t',142),('u',142),('v',142),('w',142),('x',142),('y',142),('z',142)]))" lx__100_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__100_0 = read "(False,[],-1,(('\\t',' '),[('\\t',29),('\\n',29),('\\v',29),('\\f',29),('\\r',29),(' ',29)]))" lx__101_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__101_0 = read "(False,[],-1,(('n','n'),[('n',54)]))" lx__102_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__102_0 = read "(False,[],-1,(('s','s'),[('s',244)]))" lx__103_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__103_0 = read "(False,[],-1,(('r','r'),[('r',53)]))" lx__104_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__104_0 = read "(False,[],-1,(('h','h'),[('h',224)]))" lx__105_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__105_0 = read "(False,[],-1,(('c','c'),[('c',52)]))" lx__106_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__106_0 = read "(False,[],-1,(('d','d'),[('d',243)]))" lx__107_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__107_0 = read "(False,[],-1,(('n','n'),[('n',51)]))" lx__108_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__108_0 = read "(False,[],-1,(('m','m'),[('m',50)]))" lx__109_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__109_0 = read "(False,[],-1,(('s','s'),[('s',49)]))" lx__110_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__110_0 = read "(False,[],110,(('\\n','\"'),[('\\n',-1),('\"',47)]))" lx__111_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__111_0 = read "(False,[],-1,(('-','-'),[('-',46)]))" lx__112_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__112_0 = read "(False,[],-1,(('>','>'),[('>',45)]))" lx__113_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__113_0 = read "(False,[],-1,(('>','z'),[('>',44),('A',268),('B',268),('C',268),('D',268),('E',268),('F',268),('G',268),('H',268),('I',268),('J',268),('K',268),('L',268),('M',268),('N',268),('O',268),('P',268),('Q',268),('R',268),('S',268),('T',268),('U',268),('V',268),('W',268),('X',268),('Y',268),('Z',268),('a',268),('b',268),('c',268),('d',268),('e',268),('f',268),('g',268),('h',268),('i',268),('j',268),('k',268),('l',268),('m',268),('n',268),('o',268),('p',268),('q',268),('r',268),('s',268),('t',268),('u',268),('v',268),('w',268),('x',268),('y',268),('z',268)]))" lx__114_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__114_0 = read "(False,[],-1,(('A','z'),[('A',268),('B',268),('C',268),('D',268),('E',268),('F',268),('G',268),('H',268),('I',268),('J',268),('K',268),('L',268),('M',268),('N',268),('O',268),('P',269),('Q',268),('R',268),('S',268),('T',268),('U',268),('V',268),('W',268),('X',268),('Y',268),('Z',268),('a',268),('b',268),('c',268),('d',268),('e',268),('f',268),('g',268),('h',268),('i',268),('j',268),('k',268),('l',268),('m',268),('n',268),('o',268),('p',269),('q',268),('r',268),('s',268),('t',268),('u',268),('v',268),('w',268),('x',268),('y',268),('z',268)]))" lx__115_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__115_0 = read "(False,[],-1,((';','z'),[(';',42),('A',115),('B',115),('C',115),('D',115),('E',115),('F',115),('G',115),('H',115),('I',115),('J',115),('K',115),('L',115),('M',115),('N',115),('O',115),('P',115),('Q',115),('R',115),('S',115),('T',115),('U',115),('V',115),('W',115),('X',115),('Y',115),('Z',115),('a',115),('b',115),('c',115),('d',115),('e',115),('f',115),('g',115),('h',115),('i',115),('j',115),('k',115),('l',115),('m',115),('n',115),('o',115),('p',115),('q',115),('r',115),('s',115),('t',115),('u',115),('v',115),('w',115),('x',115),('y',115),('z',115)]))" lx__116_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__116_0 = read "(False,[],29,(('}','}'),[('}',-1)]))" lx__117_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__117_0 = read "(False,[],-1,(('-','-'),[('-',34)]))" lx__118_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__118_0 = read "(False,[],-1,(('-','-'),[('-',29)]))" lx__119_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__119_0 = read "(False,[],-1,(('-','-'),[('-',32)]))" lx__120_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__120_0 = read "(False,[],-1,(('\\t','\\\\'),[('\\t',120),('\\n',120),('\\v',120),('\\f',120),('\\r',120),(' ',120),('\\\\',22)]))" lx__121_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__121_0 = read "(False,[(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',121),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',121),('~',121)]))" lx__122_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__122_0 = read "(False,[(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',122),('%',121),('\\'',121),('(',121),(')',40),('*',122),('+',122),(',',121),('-',122),('.',122),('/',122),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('<',69),('=',122),('>',69),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',122),('}',121),('~',122)]))" lx__123_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__123_0 = read "(False,[(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',122),('%',121),('\\'',121),('(',121),(')',121),('*',122),('+',122),(',',121),('-',122),('.',122),('/',122),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('<',69),('=',122),('>',69),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',122),('}',121),('~',122)]))" lx__124_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__124_0 = read "(False,[(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',121),('#',121),('$',121),('%',121),('\\'',121),('(',121),(')',121),('*',121),('+',121),(',',121),('-',28),('.',121),('/',121),('0',121),('1',121),('2',121),('3',121),('4',121),('5',121),('6',121),('7',121),('8',121),('9',121),(':',121),(';',121),('=',121),('?',121),('A',121),('B',121),('C',121),('D',121),('E',121),('F',121),('G',121),('H',121),('I',121),('J',121),('K',121),('L',121),('M',121),('N',121),('O',121),('P',121),('Q',121),('R',121),('S',121),('T',121),('U',121),('V',121),('W',121),('X',121),('Y',121),('Z',121),('[',121),('\\\\',121),(']',121),('_',121),('`',121),('a',121),('b',121),('c',121),('d',121),('e',121),('f',121),('g',121),('h',121),('i',121),('j',121),('k',121),('l',121),('m',121),('n',121),('o',121),('p',121),('q',121),('r',121),('s',121),('t',121),('u',121),('v',121),('w',121),('x',121),('y',121),('z',121),('{',121),('|',121),('}',27),('~',121)]))" lx__125_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__125_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__126_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__126_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',261),('%',125),('\\'',125),('(',125),(')',125),('*',261),('+',261),(',',125),('-',122),('.',261),('/',261),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('<',69),('=',261),('>',69),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',261),('}',121),('~',261)]))" lx__127_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__127_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',129),('1',129),('2',129),('3',129),('4',129),('5',129),('6',129),('7',129),('8',129),('9',129),(':',125),(';',125),('=',125),('?',125),('A',131),('B',131),('C',131),('D',131),('E',131),('F',131),('G',131),('H',131),('I',131),('J',131),('K',131),('L',131),('M',131),('N',131),('O',131),('P',131),('Q',131),('R',131),('S',131),('T',131),('U',131),('V',131),('W',131),('X',131),('Y',131),('Z',131),('[',125),('\\\\',125),(']',125),('_',127),('`',125),('a',129),('b',129),('c',129),('d',129),('e',129),('f',129),('g',129),('h',129),('i',129),('j',129),('k',129),('l',129),('m',129),('n',129),('o',129),('p',129),('q',129),('r',129),('s',129),('t',129),('u',129),('v',129),('w',129),('x',129),('y',129),('z',129),('{',125),('|',125),('}',121),('~',125)]))" lx__128_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__128_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(67,\"ident\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',125),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('=',125),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',125),('}',121),('~',125)]))" lx__129_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__129_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(67,\"ident\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',129),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',129),('1',129),('2',129),('3',129),('4',129),('5',129),('6',129),('7',129),('8',129),('9',129),(':',125),(';',125),('=',125),('?',125),('A',129),('B',129),('C',129),('D',129),('E',129),('F',129),('G',129),('H',129),('I',129),('J',129),('K',129),('L',129),('M',129),('N',129),('O',129),('P',129),('Q',129),('R',129),('S',129),('T',129),('U',129),('V',129),('W',129),('X',129),('Y',129),('Z',129),('[',125),('\\\\',125),(']',125),('_',129),('`',125),('a',129),('b',129),('c',129),('d',129),('e',129),('f',129),('g',129),('h',129),('i',129),('j',129),('k',129),('l',129),('m',129),('n',129),('o',129),('p',129),('q',129),('r',129),('s',129),('t',129),('u',129),('v',129),('w',129),('x',129),('y',129),('z',129),('{',125),('|',125),('}',121),('~',125)]))" lx__130_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__130_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(68,\"name\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',130),('%',125),('\\'',125),('(',125),(')',125),('*',130),('+',130),(',',125),('-',41),('.',125),('/',130),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',130),(';',125),('<',58),('=',130),('>',58),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',130),('}',121),('~',130)]))" lx__131_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__131_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing),(68,\"name\",[7,5],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',125),('%',125),('\\'',131),('(',125),(')',125),('*',125),('+',125),(',',125),('-',121),('.',125),('/',125),('0',131),('1',131),('2',131),('3',131),('4',131),('5',131),('6',131),('7',131),('8',131),('9',131),(':',125),(';',125),('=',125),('?',125),('A',131),('B',131),('C',131),('D',131),('E',131),('F',131),('G',131),('H',131),('I',131),('J',131),('K',131),('L',131),('M',131),('N',131),('O',131),('P',131),('Q',131),('R',131),('S',131),('T',131),('U',131),('V',131),('W',131),('X',131),('Y',131),('Z',131),('[',125),('\\\\',125),(']',125),('_',131),('`',125),('a',131),('b',131),('c',131),('d',131),('e',131),('f',131),('g',131),('h',131),('i',131),('j',131),('k',131),('l',131),('m',131),('n',131),('o',131),('p',131),('q',131),('r',131),('s',131),('t',131),('u',131),('v',131),('w',131),('x',131),('y',131),('z',131),('{',125),('|',125),('}',121),('~',125)]))" lx__132_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__132_0 = read "(False,[(35,\"tag\",[2,3],Nothing,Nothing)],-1,(('/','z'),[('/',112),('>',45),('A',270),('B',270),('C',270),('D',270),('E',270),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',270),('Q',270),('R',270),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',270),('c',270),('d',270),('e',270),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',270),('q',270),('r',270),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))" lx__133_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__133_0 = read "(False,[(35,\"tag\",[2,3],Nothing,Nothing)],-1,(('>','z'),[('>',43),('A',270),('B',270),('C',270),('D',270),('E',270),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',270),('Q',270),('R',270),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',270),('c',270),('d',270),('e',270),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',270),('q',270),('r',270),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))" lx__134_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__134_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing),(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',134),('\\n',139),('\\v',138),('\\f',138),('\\r',134),(' ',134)]))" lx__135_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__135_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing),(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',134),('\\n',139),('\\v',138),('\\f',138),('\\r',134),(' ',134),('$',135),('*',135),('+',135),('-',135),('/',135),(':',135),('<',135),('=',135),('>',135),('|',135),('~',135)]))" lx__136_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__136_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing),(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',134),('\\n',139),('\\v',138),('\\f',138),('\\r',134),(' ',134),('$',135),('*',135),('+',135),('-',135),('/',135),(':',93),('<',135),('=',135),('>',135),('|',135),('~',135)]))" lx__137_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__137_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing),(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t','z'),[('\\t',134),('\\n',139),('\\v',138),('\\f',138),('\\r',134),(' ',134),('\\'',137),('0',137),('1',137),('2',137),('3',137),('4',137),('5',137),('6',137),('7',137),('8',137),('9',137),('A',137),('B',137),('C',137),('D',137),('E',137),('F',137),('G',137),('H',137),('I',137),('J',137),('K',137),('L',137),('M',137),('N',137),('O',137),('P',137),('Q',137),('R',137),('S',137),('T',137),('U',137),('V',137),('W',137),('X',137),('Y',137),('Z',137),('_',137),('a',137),('b',137),('c',137),('d',137),('e',137),('f',137),('g',137),('h',137),('i',137),('j',137),('k',137),('l',137),('m',137),('n',137),('o',137),('p',137),('q',137),('r',137),('s',137),('t',137),('u',137),('v',137),('w',137),('x',137),('y',137),('z',137)]))" lx__138_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__138_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',138),('\\n',138),('\\v',138),('\\f',138),('\\r',138),(' ',138)]))" lx__139_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__139_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing)],-1,(('\\t','-'),[('\\t',139),('\\n',138),('\\v',138),('\\f',138),('\\r',139),(' ',139),('-',86)]))" lx__140_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__140_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',138),('\\n',138),('\\v',138),('\\f',138),('\\r',138),(' ',138),('$',140),('*',140),('+',140),('-',140),('/',140),(':',140),('<',140),('=',140),('>',140),('|',140),('~',140)]))" lx__141_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__141_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',138),('\\n',138),('\\v',138),('\\f',138),('\\r',138),(' ',138),('$',140),('*',140),('+',140),('-',140),('/',140),(':',94),('<',140),('=',140),('>',140),('|',140),('~',140)]))" lx__142_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__142_0 = read "(False,[(49,\"atsee\",[2],Nothing,Nothing)],-1,(('\\t','z'),[('\\t',138),('\\n',138),('\\v',138),('\\f',138),('\\r',138),(' ',138),('\\'',142),('0',142),('1',142),('2',142),('3',142),('4',142),('5',142),('6',142),('7',142),('8',142),('9',142),('A',142),('B',142),('C',142),('D',142),('E',142),('F',142),('G',142),('H',142),('I',142),('J',142),('K',142),('L',142),('M',142),('N',142),('O',142),('P',142),('Q',142),('R',142),('S',142),('T',142),('U',142),('V',142),('W',142),('X',142),('Y',142),('Z',142),('_',142),('a',142),('b',142),('c',142),('d',142),('e',142),('f',142),('g',142),('h',142),('i',142),('j',142),('k',142),('l',142),('m',142),('n',142),('o',142),('p',142),('q',142),('r',142),('s',142),('t',142),('u',142),('v',142),('w',142),('x',142),('y',142),('z',142)]))" lx__143_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__143_0 = read "(False,[(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',143),('\\n',169),('\\r',143),(' ',143)]))" lx__144_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__144_0 = read "(False,[(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',143),('\\n',169),('\\r',143),(' ',143),('$',144),('*',144),('+',144),('-',144),('/',144),(':',144),('<',144),('=',144),('>',144),('|',144),('~',144)]))" lx__145_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__145_0 = read "(False,[(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',143),('\\n',169),('\\r',143),(' ',143),('$',144),('*',144),('+',144),('-',144),('/',144),(':',88),('<',144),('=',144),('>',144),('|',144),('~',144)]))" lx__146_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__146_0 = read "(False,[(50,\"atsee3\",[3],Nothing,Nothing)],-1,(('\\t','z'),[('\\t',143),('\\n',169),('\\r',143),(' ',143),('\\'',146),('0',146),('1',146),('2',146),('3',146),('4',146),('5',146),('6',146),('7',146),('8',146),('9',146),('A',146),('B',146),('C',146),('D',146),('E',146),('F',146),('G',146),('H',146),('I',146),('J',146),('K',146),('L',146),('M',146),('N',146),('O',146),('P',146),('Q',146),('R',146),('S',146),('T',146),('U',146),('V',146),('W',146),('X',146),('Y',146),('Z',146),('_',146),('a',146),('b',146),('c',146),('d',146),('e',146),('f',146),('g',146),('h',146),('i',146),('j',146),('k',146),('l',146),('m',146),('n',146),('o',146),('p',146),('q',146),('r',146),('s',146),('t',146),('u',146),('v',146),('w',146),('x',146),('y',146),('z',146)]))" lx__147_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__147_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing),(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',147),('\\n',152),('\\v',151),('\\f',151),('\\r',147),(' ',147)]))" lx__148_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__148_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing),(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',147),('\\n',152),('\\v',151),('\\f',151),('\\r',147),(' ',147),('$',148),('*',148),('+',148),('-',148),('/',148),(':',148),('<',148),('=',148),('>',148),('|',148),('~',148)]))" lx__149_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__149_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing),(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',147),('\\n',152),('\\v',151),('\\f',151),('\\r',147),(' ',147),('$',148),('*',148),('+',148),('-',148),('/',148),(':',78),('<',148),('=',148),('>',148),('|',148),('~',148)]))" lx__150_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__150_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing),(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t','z'),[('\\t',147),('\\n',152),('\\v',151),('\\f',151),('\\r',147),(' ',147),('\\'',150),('0',150),('1',150),('2',150),('3',150),('4',150),('5',150),('6',150),('7',150),('8',150),('9',150),('A',150),('B',150),('C',150),('D',150),('E',150),('F',150),('G',150),('H',150),('I',150),('J',150),('K',150),('L',150),('M',150),('N',150),('O',150),('P',150),('Q',150),('R',150),('S',150),('T',150),('U',150),('V',150),('W',150),('X',150),('Y',150),('Z',150),('_',150),('a',150),('b',150),('c',150),('d',150),('e',150),('f',150),('g',150),('h',150),('i',150),('j',150),('k',150),('l',150),('m',150),('n',150),('o',150),('p',150),('q',150),('r',150),('s',150),('t',150),('u',150),('v',150),('w',150),('x',150),('y',150),('z',150)]))" lx__151_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__151_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',151),('\\n',151),('\\v',151),('\\f',151),('\\r',151),(' ',151)]))" lx__152_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__152_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing)],-1,(('\\t','-'),[('\\t',152),('\\n',151),('\\v',151),('\\f',151),('\\r',152),(' ',152),('-',71)]))" lx__153_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__153_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',151),('\\n',151),('\\v',151),('\\f',151),('\\r',151),(' ',151),('$',153),('*',153),('+',153),('-',153),('/',153),(':',153),('<',153),('=',153),('>',153),('|',153),('~',153)]))" lx__154_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__154_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',151),('\\n',151),('\\v',151),('\\f',151),('\\r',151),(' ',151),('$',153),('*',153),('+',153),('-',153),('/',153),(':',79),('<',153),('=',153),('>',153),('|',153),('~',153)]))" lx__155_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__155_0 = read "(False,[(51,\"atdoc\",[2],Nothing,Nothing)],-1,(('\\t','z'),[('\\t',151),('\\n',151),('\\v',151),('\\f',151),('\\r',151),(' ',151),('\\'',155),('0',155),('1',155),('2',155),('3',155),('4',155),('5',155),('6',155),('7',155),('8',155),('9',155),('A',155),('B',155),('C',155),('D',155),('E',155),('F',155),('G',155),('H',155),('I',155),('J',155),('K',155),('L',155),('M',155),('N',155),('O',155),('P',155),('Q',155),('R',155),('S',155),('T',155),('U',155),('V',155),('W',155),('X',155),('Y',155),('Z',155),('_',155),('a',155),('b',155),('c',155),('d',155),('e',155),('f',155),('g',155),('h',155),('i',155),('j',155),('k',155),('l',155),('m',155),('n',155),('o',155),('p',155),('q',155),('r',155),('s',155),('t',155),('u',155),('v',155),('w',155),('x',155),('y',155),('z',155)]))" lx__156_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__156_0 = read "(False,[(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t',' '),[('\\t',156),('\\n',170),('\\r',156),(' ',156)]))" lx__157_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__157_0 = read "(False,[(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',156),('\\n',170),('\\r',156),(' ',156),('$',157),('*',157),('+',157),('-',157),('/',157),(':',157),('<',157),('=',157),('>',157),('|',157),('~',157)]))" lx__158_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__158_0 = read "(False,[(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t','~'),[('\\t',156),('\\n',170),('\\r',156),(' ',156),('$',157),('*',157),('+',157),('-',157),('/',157),(':',73),('<',157),('=',157),('>',157),('|',157),('~',157)]))" lx__159_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__159_0 = read "(False,[(52,\"atdoc3\",[3],Nothing,Nothing)],-1,(('\\t','z'),[('\\t',156),('\\n',170),('\\r',156),(' ',156),('\\'',159),('0',159),('1',159),('2',159),('3',159),('4',159),('5',159),('6',159),('7',159),('8',159),('9',159),('A',159),('B',159),('C',159),('D',159),('E',159),('F',159),('G',159),('H',159),('I',159),('J',159),('K',159),('L',159),('M',159),('N',159),('O',159),('P',159),('Q',159),('R',159),('S',159),('T',159),('U',159),('V',159),('W',159),('X',159),('Y',159),('Z',159),('_',159),('a',159),('b',159),('c',159),('d',159),('e',159),('f',159),('g',159),('h',159),('i',159),('j',159),('k',159),('l',159),('m',159),('n',159),('o',159),('p',159),('q',159),('r',159),('s',159),('t',159),('u',159),('v',159),('w',159),('x',159),('y',159),('z',159)]))" lx__160_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__160_0 = read "(False,[],-1,(('$','~'),[('$',238),('*',238),('+',238),('-',238),('.',238),('/',238),('<',238),('=',238),('>',238),('|',238),('~',238)]))" lx__161_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__161_0 = read "(False,[],-1,(('$','~'),[('$',236),('*',236),('+',236),('-',236),('.',236),('/',236),('<',236),('=',236),('>',236),('|',236),('~',236)]))" lx__162_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__162_0 = read "(False,[],-1,(('$','~'),[('$',230),('*',230),('+',230),('-',230),('.',230),('/',230),('<',230),('=',230),('>',230),('|',230),('~',230)]))" lx__163_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__163_0 = read "(False,[],-1,(('$','~'),[('$',220),('*',220),('+',220),('-',220),('.',220),('/',220),('<',220),('=',220),('>',220),('|',220),('~',220)]))" lx__164_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__164_0 = read "(False,[],-1,(('$','~'),[('$',218),('*',218),('+',218),('-',218),('.',218),('/',218),('<',218),('=',218),('>',218),('|',218),('~',218)]))" lx__165_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__165_0 = read "(False,[],-1,(('$','~'),[('$',180),('*',180),('+',180),('-',180),('.',180),('/',180),('<',180),('=',180),('>',180),('|',180),('~',180)]))" lx__166_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__166_0 = read "(False,[],-1,(('$','~'),[('$',69),('*',69),('+',69),('-',69),('.',69),('/',69),('<',69),('=',69),('>',69),('|',69),('~',69)]))" lx__167_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__167_0 = read "(False,[],-1,(('\\t','-'),[('\\t',167),('\\r',167),(' ',167),('-',119)]))" lx__168_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__168_0 = read "(False,[],-1,(('\\t','-'),[('\\t',168),('\\r',168),(' ',168),('-',111)]))" lx__169_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__169_0 = read "(False,[],-1,(('\\t','-'),[('\\t',169),('\\r',169),(' ',169),('-',86)]))" lx__170_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__170_0 = read "(False,[],-1,(('\\t','-'),[('\\t',170),('\\r',170),(' ',170),('-',71)]))" lx__171_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__171_0 = read "(False,[],-1,(('$','~'),[('$',172),(')',156),('*',172),('+',172),('-',172),('/',172),(':',178),('<',172),('=',172),('>',172),('|',172),('~',172)]))" lx__172_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__172_0 = read "(False,[],-1,(('$','~'),[('$',172),(')',156),('*',172),('+',172),('-',172),('/',172),(':',172),('<',172),('=',172),('>',172),('|',172),('~',172)]))" lx__173_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__173_0 = read "(False,[],-1,(('$','~'),[('$',234),('*',234),('+',234),('-',234),('/',234),(':',234),('<',234),('=',234),('>',234),('|',234),('~',234)]))" lx__174_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__174_0 = read "(False,[],-1,(('$','~'),[('$',232),('*',232),('+',232),('-',232),('/',232),(':',232),('<',232),('=',232),('>',232),('|',232),('~',232)]))" lx__175_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__175_0 = read "(False,[],-1,(('$','~'),[('$',228),('*',228),('+',228),('-',228),('/',228),(':',228),('<',228),('=',228),('>',228),('|',228),('~',228)]))" lx__176_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__176_0 = read "(False,[],-1,(('$','~'),[('$',216),('*',216),('+',216),('-',216),('/',216),(':',216),('<',216),('=',216),('>',216),('|',216),('~',216)]))" lx__177_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__177_0 = read "(False,[],-1,(('$','~'),[('$',214),('*',214),('+',214),('-',214),('/',214),(':',214),('<',214),('=',214),('>',214),('|',214),('~',214)]))" lx__178_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__178_0 = read "(False,[],-1,(('$','~'),[('$',172),('*',172),('+',172),('-',172),('/',172),(':',172),('<',172),('=',172),('>',172),('|',172),('~',172)]))" lx__179_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__179_0 = read "(False,[],-1,(('$','~'),[('$',180),(')',156),('*',180),('+',180),('-',180),('.',165),('/',180),('<',180),('=',180),('>',180),('|',180),('~',180)]))" lx__180_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__180_0 = read "(False,[],-1,(('$','~'),[('$',180),(')',156),('*',180),('+',180),('-',180),('.',180),('/',180),('<',180),('=',180),('>',180),('|',180),('~',180)]))" lx__181_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__181_0 = read "(False,[],-1,(('0','z'),[('0',92),('1',92),('2',92),('3',92),('4',92),('5',92),('6',92),('7',92),('8',92),('9',92),('A',92),('B',92),('C',92),('D',92),('E',92),('F',92),('G',92),('H',92),('I',92),('J',92),('K',92),('L',92),('M',92),('N',92),('O',92),('P',92),('Q',92),('R',92),('S',92),('T',92),('U',92),('V',92),('W',92),('X',92),('Y',92),('Z',92),('_',181),('a',92),('b',92),('c',92),('d',92),('e',92),('f',92),('g',92),('h',92),('i',92),('j',92),('k',92),('l',92),('m',92),('n',92),('o',92),('p',92),('q',92),('r',92),('s',92),('t',92),('u',92),('v',92),('w',92),('x',92),('y',92),('z',92)]))" lx__182_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__182_0 = read "(False,[],-1,(('0','z'),[('0',91),('1',91),('2',91),('3',91),('4',91),('5',91),('6',91),('7',91),('8',91),('9',91),('A',91),('B',91),('C',91),('D',91),('E',91),('F',91),('G',91),('H',91),('I',91),('J',91),('K',91),('L',91),('M',91),('N',91),('O',91),('P',91),('Q',91),('R',91),('S',91),('T',91),('U',91),('V',91),('W',91),('X',91),('Y',91),('Z',91),('_',182),('a',91),('b',91),('c',91),('d',91),('e',91),('f',91),('g',91),('h',91),('i',91),('j',91),('k',91),('l',91),('m',91),('n',91),('o',91),('p',91),('q',91),('r',91),('s',91),('t',91),('u',91),('v',91),('w',91),('x',91),('y',91),('z',91)]))" lx__183_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__183_0 = read "(False,[],-1,(('0','z'),[('0',87),('1',87),('2',87),('3',87),('4',87),('5',87),('6',87),('7',87),('8',87),('9',87),('A',87),('B',87),('C',87),('D',87),('E',87),('F',87),('G',87),('H',87),('I',87),('J',87),('K',87),('L',87),('M',87),('N',87),('O',87),('P',87),('Q',87),('R',87),('S',87),('T',87),('U',87),('V',87),('W',87),('X',87),('Y',87),('Z',87),('_',183),('a',87),('b',87),('c',87),('d',87),('e',87),('f',87),('g',87),('h',87),('i',87),('j',87),('k',87),('l',87),('m',87),('n',87),('o',87),('p',87),('q',87),('r',87),('s',87),('t',87),('u',87),('v',87),('w',87),('x',87),('y',87),('z',87)]))" lx__184_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__184_0 = read "(False,[],-1,(('0','z'),[('0',77),('1',77),('2',77),('3',77),('4',77),('5',77),('6',77),('7',77),('8',77),('9',77),('A',77),('B',77),('C',77),('D',77),('E',77),('F',77),('G',77),('H',77),('I',77),('J',77),('K',77),('L',77),('M',77),('N',77),('O',77),('P',77),('Q',77),('R',77),('S',77),('T',77),('U',77),('V',77),('W',77),('X',77),('Y',77),('Z',77),('_',184),('a',77),('b',77),('c',77),('d',77),('e',77),('f',77),('g',77),('h',77),('i',77),('j',77),('k',77),('l',77),('m',77),('n',77),('o',77),('p',77),('q',77),('r',77),('s',77),('t',77),('u',77),('v',77),('w',77),('x',77),('y',77),('z',77)]))" lx__185_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__185_0 = read "(False,[],-1,(('0','z'),[('0',76),('1',76),('2',76),('3',76),('4',76),('5',76),('6',76),('7',76),('8',76),('9',76),('A',76),('B',76),('C',76),('D',76),('E',76),('F',76),('G',76),('H',76),('I',76),('J',76),('K',76),('L',76),('M',76),('N',76),('O',76),('P',76),('Q',76),('R',76),('S',76),('T',76),('U',76),('V',76),('W',76),('X',76),('Y',76),('Z',76),('_',185),('a',76),('b',76),('c',76),('d',76),('e',76),('f',76),('g',76),('h',76),('i',76),('j',76),('k',76),('l',76),('m',76),('n',76),('o',76),('p',76),('q',76),('r',76),('s',76),('t',76),('u',76),('v',76),('w',76),('x',76),('y',76),('z',76)]))" lx__186_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__186_0 = read "(False,[],-1,(('0','z'),[('0',72),('1',72),('2',72),('3',72),('4',72),('5',72),('6',72),('7',72),('8',72),('9',72),('A',72),('B',72),('C',72),('D',72),('E',72),('F',72),('G',72),('H',72),('I',72),('J',72),('K',72),('L',72),('M',72),('N',72),('O',72),('P',72),('Q',72),('R',72),('S',72),('T',72),('U',72),('V',72),('W',72),('X',72),('Y',72),('Z',72),('_',186),('a',72),('b',72),('c',72),('d',72),('e',72),('f',72),('g',72),('h',72),('i',72),('j',72),('k',72),('l',72),('m',72),('n',72),('o',72),('p',72),('q',72),('r',72),('s',72),('t',72),('u',72),('v',72),('w',72),('x',72),('y',72),('z',72)]))" lx__187_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__187_0 = read "(False,[],-1,(('$','~'),[('$',160),('*',160),('+',160),('-',160),('.',237),('/',160),(':',233),('<',160),('=',160),('>',160),('A',92),('B',92),('C',92),('D',92),('E',92),('F',92),('G',92),('H',92),('I',92),('J',92),('K',92),('L',92),('M',92),('N',92),('O',92),('P',92),('Q',92),('R',92),('S',92),('T',92),('U',92),('V',92),('W',92),('X',92),('Y',92),('Z',92),('_',181),('a',92),('b',92),('c',92),('d',92),('e',92),('f',92),('g',92),('h',92),('i',92),('j',92),('k',92),('l',92),('m',92),('n',92),('o',92),('p',92),('q',92),('r',92),('s',92),('t',92),('u',92),('v',92),('w',92),('x',92),('y',92),('z',92),('|',160),('~',160)]))" lx__188_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__188_0 = read "(False,[],-1,(('$','~'),[('$',161),('*',161),('+',161),('-',161),('.',235),('/',161),(':',231),('<',161),('=',161),('>',161),('A',91),('B',91),('C',91),('D',91),('E',91),('F',91),('G',91),('H',91),('I',91),('J',91),('K',91),('L',91),('M',91),('N',91),('O',91),('P',91),('Q',91),('R',91),('S',91),('T',91),('U',91),('V',91),('W',91),('X',91),('Y',91),('Z',91),('_',182),('a',91),('b',91),('c',91),('d',91),('e',91),('f',91),('g',91),('h',91),('i',91),('j',91),('k',91),('l',91),('m',91),('n',91),('o',91),('p',91),('q',91),('r',91),('s',91),('t',91),('u',91),('v',91),('w',91),('x',91),('y',91),('z',91),('|',161),('~',161)]))" lx__189_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__189_0 = read "(False,[],-1,(('$','~'),[('$',162),('*',162),('+',162),('-',162),('.',229),('/',162),(':',227),('<',162),('=',162),('>',162),('A',87),('B',87),('C',87),('D',87),('E',87),('F',87),('G',87),('H',87),('I',87),('J',87),('K',87),('L',87),('M',87),('N',87),('O',87),('P',87),('Q',87),('R',87),('S',87),('T',87),('U',87),('V',87),('W',87),('X',87),('Y',87),('Z',87),('_',183),('a',87),('b',87),('c',87),('d',87),('e',87),('f',87),('g',87),('h',87),('i',87),('j',87),('k',87),('l',87),('m',87),('n',87),('o',87),('p',87),('q',87),('r',87),('s',87),('t',87),('u',87),('v',87),('w',87),('x',87),('y',87),('z',87),('|',162),('~',162)]))" lx__190_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__190_0 = read "(False,[],-1,(('$','~'),[('$',163),('*',163),('+',163),('-',163),('.',219),('/',163),(':',215),('<',163),('=',163),('>',163),('A',77),('B',77),('C',77),('D',77),('E',77),('F',77),('G',77),('H',77),('I',77),('J',77),('K',77),('L',77),('M',77),('N',77),('O',77),('P',77),('Q',77),('R',77),('S',77),('T',77),('U',77),('V',77),('W',77),('X',77),('Y',77),('Z',77),('_',184),('a',77),('b',77),('c',77),('d',77),('e',77),('f',77),('g',77),('h',77),('i',77),('j',77),('k',77),('l',77),('m',77),('n',77),('o',77),('p',77),('q',77),('r',77),('s',77),('t',77),('u',77),('v',77),('w',77),('x',77),('y',77),('z',77),('|',163),('~',163)]))" lx__191_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__191_0 = read "(False,[],-1,(('$','~'),[('$',164),('*',164),('+',164),('-',164),('.',217),('/',164),(':',213),('<',164),('=',164),('>',164),('A',76),('B',76),('C',76),('D',76),('E',76),('F',76),('G',76),('H',76),('I',76),('J',76),('K',76),('L',76),('M',76),('N',76),('O',76),('P',76),('Q',76),('R',76),('S',76),('T',76),('U',76),('V',76),('W',76),('X',76),('Y',76),('Z',76),('_',185),('a',76),('b',76),('c',76),('d',76),('e',76),('f',76),('g',76),('h',76),('i',76),('j',76),('k',76),('l',76),('m',76),('n',76),('o',76),('p',76),('q',76),('r',76),('s',76),('t',76),('u',76),('v',76),('w',76),('x',76),('y',76),('z',76),('|',164),('~',164)]))" lx__192_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__192_0 = read "(False,[],-1,(('$','~'),[('$',165),('*',165),('+',165),('-',165),('.',179),('/',165),(':',171),('<',165),('=',165),('>',165),('A',72),('B',72),('C',72),('D',72),('E',72),('F',72),('G',72),('H',72),('I',72),('J',72),('K',72),('L',72),('M',72),('N',72),('O',72),('P',72),('Q',72),('R',72),('S',72),('T',72),('U',72),('V',72),('W',72),('X',72),('Y',72),('Z',72),('_',186),('a',72),('b',72),('c',72),('d',72),('e',72),('f',72),('g',72),('h',72),('i',72),('j',72),('k',72),('l',72),('m',72),('n',72),('o',72),('p',72),('q',72),('r',72),('s',72),('t',72),('u',72),('v',72),('w',72),('x',72),('y',72),('z',72),('|',165),('~',165)]))" lx__193_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__193_0 = read "(False,[],-1,(('\\'','z'),[('\\'',193),('.',187),('0',193),('1',193),('2',193),('3',193),('4',193),('5',193),('6',193),('7',193),('8',193),('9',193),('A',193),('B',193),('C',193),('D',193),('E',193),('F',193),('G',193),('H',193),('I',193),('J',193),('K',193),('L',193),('M',193),('N',193),('O',193),('P',193),('Q',193),('R',193),('S',193),('T',193),('U',193),('V',193),('W',193),('X',193),('Y',193),('Z',193),('_',193),('a',193),('b',193),('c',193),('d',193),('e',193),('f',193),('g',193),('h',193),('i',193),('j',193),('k',193),('l',193),('m',193),('n',193),('o',193),('p',193),('q',193),('r',193),('s',193),('t',193),('u',193),('v',193),('w',193),('x',193),('y',193),('z',193)]))" lx__194_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__194_0 = read "(False,[],-1,(('\\'','z'),[('\\'',194),('.',188),('0',194),('1',194),('2',194),('3',194),('4',194),('5',194),('6',194),('7',194),('8',194),('9',194),('A',194),('B',194),('C',194),('D',194),('E',194),('F',194),('G',194),('H',194),('I',194),('J',194),('K',194),('L',194),('M',194),('N',194),('O',194),('P',194),('Q',194),('R',194),('S',194),('T',194),('U',194),('V',194),('W',194),('X',194),('Y',194),('Z',194),('_',194),('a',194),('b',194),('c',194),('d',194),('e',194),('f',194),('g',194),('h',194),('i',194),('j',194),('k',194),('l',194),('m',194),('n',194),('o',194),('p',194),('q',194),('r',194),('s',194),('t',194),('u',194),('v',194),('w',194),('x',194),('y',194),('z',194)]))" lx__195_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__195_0 = read "(False,[],-1,(('\\'','z'),[('\\'',195),('.',189),('0',195),('1',195),('2',195),('3',195),('4',195),('5',195),('6',195),('7',195),('8',195),('9',195),('A',195),('B',195),('C',195),('D',195),('E',195),('F',195),('G',195),('H',195),('I',195),('J',195),('K',195),('L',195),('M',195),('N',195),('O',195),('P',195),('Q',195),('R',195),('S',195),('T',195),('U',195),('V',195),('W',195),('X',195),('Y',195),('Z',195),('_',195),('a',195),('b',195),('c',195),('d',195),('e',195),('f',195),('g',195),('h',195),('i',195),('j',195),('k',195),('l',195),('m',195),('n',195),('o',195),('p',195),('q',195),('r',195),('s',195),('t',195),('u',195),('v',195),('w',195),('x',195),('y',195),('z',195)]))" lx__196_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__196_0 = read "(False,[],-1,(('\\'','z'),[('\\'',196),('.',190),('0',196),('1',196),('2',196),('3',196),('4',196),('5',196),('6',196),('7',196),('8',196),('9',196),('A',196),('B',196),('C',196),('D',196),('E',196),('F',196),('G',196),('H',196),('I',196),('J',196),('K',196),('L',196),('M',196),('N',196),('O',196),('P',196),('Q',196),('R',196),('S',196),('T',196),('U',196),('V',196),('W',196),('X',196),('Y',196),('Z',196),('_',196),('a',196),('b',196),('c',196),('d',196),('e',196),('f',196),('g',196),('h',196),('i',196),('j',196),('k',196),('l',196),('m',196),('n',196),('o',196),('p',196),('q',196),('r',196),('s',196),('t',196),('u',196),('v',196),('w',196),('x',196),('y',196),('z',196)]))" lx__197_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__197_0 = read "(False,[],-1,(('\\'','z'),[('\\'',197),('.',191),('0',197),('1',197),('2',197),('3',197),('4',197),('5',197),('6',197),('7',197),('8',197),('9',197),('A',197),('B',197),('C',197),('D',197),('E',197),('F',197),('G',197),('H',197),('I',197),('J',197),('K',197),('L',197),('M',197),('N',197),('O',197),('P',197),('Q',197),('R',197),('S',197),('T',197),('U',197),('V',197),('W',197),('X',197),('Y',197),('Z',197),('_',197),('a',197),('b',197),('c',197),('d',197),('e',197),('f',197),('g',197),('h',197),('i',197),('j',197),('k',197),('l',197),('m',197),('n',197),('o',197),('p',197),('q',197),('r',197),('s',197),('t',197),('u',197),('v',197),('w',197),('x',197),('y',197),('z',197)]))" lx__198_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__198_0 = read "(False,[],-1,(('\\'','z'),[('\\'',198),('.',192),('0',198),('1',198),('2',198),('3',198),('4',198),('5',198),('6',198),('7',198),('8',198),('9',198),('A',198),('B',198),('C',198),('D',198),('E',198),('F',198),('G',198),('H',198),('I',198),('J',198),('K',198),('L',198),('M',198),('N',198),('O',198),('P',198),('Q',198),('R',198),('S',198),('T',198),('U',198),('V',198),('W',198),('X',198),('Y',198),('Z',198),('_',198),('a',198),('b',198),('c',198),('d',198),('e',198),('f',198),('g',198),('h',198),('i',198),('j',198),('k',198),('l',198),('m',198),('n',198),('o',198),('p',198),('q',198),('r',198),('s',198),('t',198),('u',198),('v',198),('w',198),('x',198),('y',198),('z',198)]))" lx__199_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__199_0 = read "(False,[],-1,(('A','_'),[('A',193),('B',193),('C',193),('D',193),('E',193),('F',193),('G',193),('H',193),('I',193),('J',193),('K',193),('L',193),('M',193),('N',193),('O',193),('P',193),('Q',193),('R',193),('S',193),('T',193),('U',193),('V',193),('W',193),('X',193),('Y',193),('Z',193),('_',199)]))" lx__200_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__200_0 = read "(False,[],-1,(('A','_'),[('A',194),('B',194),('C',194),('D',194),('E',194),('F',194),('G',194),('H',194),('I',194),('J',194),('K',194),('L',194),('M',194),('N',194),('O',194),('P',194),('Q',194),('R',194),('S',194),('T',194),('U',194),('V',194),('W',194),('X',194),('Y',194),('Z',194),('_',200)]))" lx__201_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__201_0 = read "(False,[],-1,(('A','_'),[('A',195),('B',195),('C',195),('D',195),('E',195),('F',195),('G',195),('H',195),('I',195),('J',195),('K',195),('L',195),('M',195),('N',195),('O',195),('P',195),('Q',195),('R',195),('S',195),('T',195),('U',195),('V',195),('W',195),('X',195),('Y',195),('Z',195),('_',201)]))" lx__202_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__202_0 = read "(False,[],-1,(('A','_'),[('A',196),('B',196),('C',196),('D',196),('E',196),('F',196),('G',196),('H',196),('I',196),('J',196),('K',196),('L',196),('M',196),('N',196),('O',196),('P',196),('Q',196),('R',196),('S',196),('T',196),('U',196),('V',196),('W',196),('X',196),('Y',196),('Z',196),('_',202)]))" lx__203_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__203_0 = read "(False,[],-1,(('A','_'),[('A',197),('B',197),('C',197),('D',197),('E',197),('F',197),('G',197),('H',197),('I',197),('J',197),('K',197),('L',197),('M',197),('N',197),('O',197),('P',197),('Q',197),('R',197),('S',197),('T',197),('U',197),('V',197),('W',197),('X',197),('Y',197),('Z',197),('_',203)]))" lx__204_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__204_0 = read "(False,[],-1,(('A','_'),[('A',198),('B',198),('C',198),('D',198),('E',198),('F',198),('G',198),('H',198),('I',198),('J',198),('K',198),('L',198),('M',198),('N',198),('O',198),('P',198),('Q',198),('R',198),('S',198),('T',198),('U',198),('V',198),('W',198),('X',198),('Y',198),('Z',198),('_',204)]))" lx__205_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__205_0 = read "(False,[],-1,(('$','~'),[('$',160),('*',160),('+',160),('-',160),('.',237),('/',160),('<',160),('=',160),('>',160),('A',193),('B',193),('C',193),('D',193),('E',193),('F',193),('G',193),('H',193),('I',193),('J',193),('K',193),('L',193),('M',193),('N',193),('O',193),('P',193),('Q',193),('R',193),('S',193),('T',193),('U',193),('V',193),('W',193),('X',193),('Y',193),('Z',193),('_',199),('|',160),('~',160)]))" lx__206_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__206_0 = read "(False,[],-1,(('$','~'),[('$',161),('*',161),('+',161),('-',161),('.',235),('/',161),('<',161),('=',161),('>',161),('A',194),('B',194),('C',194),('D',194),('E',194),('F',194),('G',194),('H',194),('I',194),('J',194),('K',194),('L',194),('M',194),('N',194),('O',194),('P',194),('Q',194),('R',194),('S',194),('T',194),('U',194),('V',194),('W',194),('X',194),('Y',194),('Z',194),('_',200),('|',161),('~',161)]))" lx__207_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__207_0 = read "(False,[],-1,(('$','~'),[('$',162),('*',162),('+',162),('-',162),('.',229),('/',162),('<',162),('=',162),('>',162),('A',195),('B',195),('C',195),('D',195),('E',195),('F',195),('G',195),('H',195),('I',195),('J',195),('K',195),('L',195),('M',195),('N',195),('O',195),('P',195),('Q',195),('R',195),('S',195),('T',195),('U',195),('V',195),('W',195),('X',195),('Y',195),('Z',195),('_',201),('|',162),('~',162)]))" lx__208_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__208_0 = read "(False,[],-1,(('$','~'),[('$',163),('*',163),('+',163),('-',163),('.',219),('/',163),('<',163),('=',163),('>',163),('A',196),('B',196),('C',196),('D',196),('E',196),('F',196),('G',196),('H',196),('I',196),('J',196),('K',196),('L',196),('M',196),('N',196),('O',196),('P',196),('Q',196),('R',196),('S',196),('T',196),('U',196),('V',196),('W',196),('X',196),('Y',196),('Z',196),('_',202),('|',163),('~',163)]))" lx__209_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__209_0 = read "(False,[],-1,(('$','~'),[('$',164),('*',164),('+',164),('-',164),('.',217),('/',164),('<',164),('=',164),('>',164),('A',197),('B',197),('C',197),('D',197),('E',197),('F',197),('G',197),('H',197),('I',197),('J',197),('K',197),('L',197),('M',197),('N',197),('O',197),('P',197),('Q',197),('R',197),('S',197),('T',197),('U',197),('V',197),('W',197),('X',197),('Y',197),('Z',197),('_',203),('|',164),('~',164)]))" lx__210_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__210_0 = read "(False,[],-1,(('$','~'),[('$',165),('*',165),('+',165),('-',165),('.',179),('/',165),('<',165),('=',165),('>',165),('A',198),('B',198),('C',198),('D',198),('E',198),('F',198),('G',198),('H',198),('I',198),('J',198),('K',198),('L',198),('M',198),('N',198),('O',198),('P',198),('Q',198),('R',198),('S',198),('T',198),('U',198),('V',198),('W',198),('X',198),('Y',198),('Z',198),('_',204),('|',165),('~',165)]))" lx__211_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__211_0 = read "(False,[],-1,(('-','-'),[('-',90)]))" lx__212_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__212_0 = read "(False,[],-1,(('-','-'),[('-',75)]))" lx__213_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__213_0 = read "(False,[],-1,(('$','~'),[('$',214),(')',147),('*',214),('+',214),('-',214),('/',214),(':',177),('<',214),('=',214),('>',214),('|',214),('~',214)]))" lx__214_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__214_0 = read "(False,[],-1,(('$','~'),[('$',214),(')',147),('*',214),('+',214),('-',214),('/',214),(':',214),('<',214),('=',214),('>',214),('|',214),('~',214)]))" lx__215_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__215_0 = read "(False,[],-1,(('$','~'),[('$',216),(')',151),('*',216),('+',216),('-',216),('/',216),(':',176),('<',216),('=',216),('>',216),('|',216),('~',216)]))" lx__216_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__216_0 = read "(False,[],-1,(('$','~'),[('$',216),(')',151),('*',216),('+',216),('-',216),('/',216),(':',216),('<',216),('=',216),('>',216),('|',216),('~',216)]))" lx__217_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__217_0 = read "(False,[],-1,(('$','~'),[('$',218),(')',147),('*',218),('+',218),('-',218),('.',164),('/',218),('<',218),('=',218),('>',218),('|',218),('~',218)]))" lx__218_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__218_0 = read "(False,[],-1,(('$','~'),[('$',218),(')',147),('*',218),('+',218),('-',218),('.',218),('/',218),('<',218),('=',218),('>',218),('|',218),('~',218)]))" lx__219_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__219_0 = read "(False,[],-1,(('$','~'),[('$',220),(')',151),('*',220),('+',220),('-',220),('.',163),('/',220),('<',220),('=',220),('>',220),('|',220),('~',220)]))" lx__220_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__220_0 = read "(False,[],-1,(('$','~'),[('$',220),(')',151),('*',220),('+',220),('-',220),('.',220),('/',220),('<',220),('=',220),('>',220),('|',220),('~',220)]))" lx__221_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__221_0 = read "(False,[],-1,(('\\t',' '),[('\\t',221),('\\n',120),('\\v',221),('\\f',221),('\\r',221),(' ',221)]))" lx__222_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__222_0 = read "(False,[],-1,(('\\t',' '),[('\\t',98),('\\n',97),('\\v',99),('\\f',99),('\\r',98),(' ',98)]))" lx__223_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__223_0 = read "(False,[],-1,(('\\t',' '),[('\\t',83),('\\n',82),('\\v',84),('\\f',84),('\\r',83),(' ',83)]))" lx__224_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__224_0 = read "(False,[],-1,(('o','o'),[('o',103)]))" lx__225_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__225_0 = read "(False,[],-1,(('o','o'),[('o',101)]))" lx__226_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__226_0 = read "(False,[],-1,(('o','o'),[('o',85)]))" lx__227_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__227_0 = read "(False,[],-1,(('$','~'),[('$',228),(')',143),('*',228),('+',228),('-',228),('/',228),(':',175),('<',228),('=',228),('>',228),('|',228),('~',228)]))" lx__228_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__228_0 = read "(False,[],-1,(('$','~'),[('$',228),(')',143),('*',228),('+',228),('-',228),('/',228),(':',228),('<',228),('=',228),('>',228),('|',228),('~',228)]))" lx__229_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__229_0 = read "(False,[],-1,(('$','~'),[('$',230),(')',143),('*',230),('+',230),('-',230),('.',162),('/',230),('<',230),('=',230),('>',230),('|',230),('~',230)]))" lx__230_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__230_0 = read "(False,[],-1,(('$','~'),[('$',230),(')',143),('*',230),('+',230),('-',230),('.',230),('/',230),('<',230),('=',230),('>',230),('|',230),('~',230)]))" lx__231_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__231_0 = read "(False,[],-1,(('$','~'),[('$',232),(')',134),('*',232),('+',232),('-',232),('/',232),(':',174),('<',232),('=',232),('>',232),('|',232),('~',232)]))" lx__232_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__232_0 = read "(False,[],-1,(('$','~'),[('$',232),(')',134),('*',232),('+',232),('-',232),('/',232),(':',232),('<',232),('=',232),('>',232),('|',232),('~',232)]))" lx__233_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__233_0 = read "(False,[],-1,(('$','~'),[('$',234),(')',138),('*',234),('+',234),('-',234),('/',234),(':',173),('<',234),('=',234),('>',234),('|',234),('~',234)]))" lx__234_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__234_0 = read "(False,[],-1,(('$','~'),[('$',234),(')',138),('*',234),('+',234),('-',234),('/',234),(':',234),('<',234),('=',234),('>',234),('|',234),('~',234)]))" lx__235_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__235_0 = read "(False,[],-1,(('$','~'),[('$',236),(')',134),('*',236),('+',236),('-',236),('.',161),('/',236),('<',236),('=',236),('>',236),('|',236),('~',236)]))" lx__236_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__236_0 = read "(False,[],-1,(('$','~'),[('$',236),(')',134),('*',236),('+',236),('-',236),('.',236),('/',236),('<',236),('=',236),('>',236),('|',236),('~',236)]))" lx__237_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__237_0 = read "(False,[],-1,(('$','~'),[('$',238),(')',138),('*',238),('+',238),('-',238),('.',160),('/',238),('<',238),('=',238),('>',238),('|',238),('~',238)]))" lx__238_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__238_0 = read "(False,[],-1,(('$','~'),[('$',238),(')',138),('*',238),('+',238),('-',238),('.',238),('/',238),('<',238),('=',238),('>',238),('|',238),('~',238)]))" lx__239_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__239_0 = read "(False,[],-1,(('e','e'),[('e',248)]))" lx__240_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__240_0 = read "(False,[],-1,(('e','e'),[('e',247)]))" lx__241_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__241_0 = read "(False,[],-1,(('e','e'),[('e',242)]))" lx__242_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__242_0 = read "(False,[],-1,(('e','e'),[('e',222)]))" lx__243_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__243_0 = read "(False,[],-1,(('i','i'),[('i',105)]))" lx__244_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__244_0 = read "(False,[],-1,(('i','i'),[('i',225)]))" lx__245_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__245_0 = read "(False,[],-1,(('r','r'),[('r',253)]))" lx__246_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__246_0 = read "(False,[],-1,(('r','r'),[('r',107)]))" lx__247_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__247_0 = read "(False,[],-1,(('r','r'),[('r',102)]))" lx__248_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__248_0 = read "(False,[],-1,(('t','t'),[('t',250)]))" lx__249_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__249_0 = read "(False,[],-1,(('t','t'),[('t',104)]))" lx__250_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__250_0 = read "(False,[],-1,(('u','u'),[('u',246)]))" lx__251_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__251_0 = read "(False,[],-1,(('u','u'),[('u',249)]))" lx__252_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__252_0 = read "(False,[],-1,(('a','a'),[('a',245)]))" lx__253_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__253_0 = read "(False,[],-1,(('a','a'),[('a',108)]))" lx__254_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__254_0 = read "(False,[],-1,(('a','a'),[('a',106)]))" lx__255_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__255_0 = read "(False,[],-1,(('n','n'),[('n',109)]))" lx__256_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__256_0 = read "(False,[],-1,(('n','n'),[('n',254)]))" lx__257_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__257_0 = read "(False,[],-1,(('>','z'),[('>',48),('A',268),('B',268),('C',268),('D',268),('E',113),('F',268),('G',268),('H',268),('I',268),('J',268),('K',268),('L',268),('M',268),('N',268),('O',268),('P',268),('Q',268),('R',268),('S',268),('T',268),('U',268),('V',268),('W',268),('X',268),('Y',268),('Z',268),('a',268),('b',268),('c',268),('d',268),('e',113),('f',268),('g',268),('h',268),('i',268),('j',268),('k',268),('l',268),('m',268),('n',268),('o',268),('p',268),('q',268),('r',268),('s',268),('t',268),('u',268),('v',268),('w',268),('x',268),('y',268),('z',268)]))" lx__258_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__258_0 = read "(False,[],29,(('-','-'),[('-',259)]))" lx__259_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__259_0 = read "(False,[],29,(('-','-'),[('-',118)]))" lx__260_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__260_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',261),('%',125),('\\'',125),('(',125),(')',128),('*',261),('+',261),(',',125),('-',122),('.',126),('/',261),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('<',69),('=',261),('>',69),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',261),('}',121),('~',261)]))" lx__261_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__261_0 = read "(False,[(27,\"textOld\",[2],Nothing,Nothing),(29,\"text\",[3],Nothing,Nothing)],-1,(('!','~'),[('!',125),('#',125),('$',261),('%',125),('\\'',125),('(',125),(')',128),('*',261),('+',261),(',',125),('-',122),('.',261),('/',261),('0',125),('1',125),('2',125),('3',125),('4',125),('5',125),('6',125),('7',125),('8',125),('9',125),(':',125),(';',125),('<',69),('=',261),('>',69),('?',125),('A',125),('B',125),('C',125),('D',125),('E',125),('F',125),('G',125),('H',125),('I',125),('J',125),('K',125),('L',125),('M',125),('N',125),('O',125),('P',125),('Q',125),('R',125),('S',125),('T',125),('U',125),('V',125),('W',125),('X',125),('Y',125),('Z',125),('[',125),('\\\\',125),(']',125),('_',125),('`',125),('a',125),('b',125),('c',125),('d',125),('e',125),('f',125),('g',125),('h',125),('i',125),('j',125),('k',125),('l',125),('m',125),('n',125),('o',125),('p',125),('q',125),('r',125),('s',125),('t',125),('u',125),('v',125),('w',125),('x',125),('y',125),('z',125),('{',125),('|',261),('}',121),('~',261)]))" lx__262_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__262_0 = read "(False,[(35,\"tag\",[2,3],Nothing,Nothing)],-1,(('A','z'),[('A',270),('B',270),('C',270),('D',270),('E',133),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',270),('Q',270),('R',270),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',270),('c',270),('d',270),('e',133),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',270),('q',270),('r',270),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))" lx__263_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__263_0 = read "(False,[(35,\"tag\",[2,3],Nothing,Nothing)],-1,(('A','z'),[('A',270),('B',270),('C',270),('D',270),('E',270),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',270),('Q',270),('R',132),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',270),('c',270),('d',270),('e',270),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',270),('q',270),('r',132),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))" lx__264_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__264_0 = read "(False,[],-1,(('\\t','-'),[('\\t',264),('\\r',264),(' ',264),('-',212)]))" lx__265_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__265_0 = read "(False,[],-1,(('\\t','-'),[('\\t',265),('\\r',265),(' ',265),('-',211)]))" lx__266_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__266_0 = read "(False,[],-1,(('o','o'),[('o',256)]))" lx__267_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__267_0 = read "(False,[],-1,(('o','o'),[('o',255)]))" lx__268_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__268_0 = read "(False,[],-1,(('>','z'),[('>',48),('A',268),('B',268),('C',268),('D',268),('E',268),('F',268),('G',268),('H',268),('I',268),('J',268),('K',268),('L',268),('M',268),('N',268),('O',268),('P',268),('Q',268),('R',268),('S',268),('T',268),('U',268),('V',268),('W',268),('X',268),('Y',268),('Z',268),('a',268),('b',268),('c',268),('d',268),('e',268),('f',268),('g',268),('h',268),('i',268),('j',268),('k',268),('l',268),('m',268),('n',268),('o',268),('p',268),('q',268),('r',268),('s',268),('t',268),('u',268),('v',268),('w',268),('x',268),('y',268),('z',268)]))" lx__269_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__269_0 = read "(False,[],-1,(('>','z'),[('>',48),('A',268),('B',268),('C',268),('D',268),('E',268),('F',268),('G',268),('H',268),('I',268),('J',268),('K',268),('L',268),('M',268),('N',268),('O',268),('P',268),('Q',268),('R',257),('S',268),('T',268),('U',268),('V',268),('W',268),('X',268),('Y',268),('Z',268),('a',268),('b',268),('c',268),('d',268),('e',268),('f',268),('g',268),('h',268),('i',268),('j',268),('k',268),('l',268),('m',268),('n',268),('o',268),('p',268),('q',268),('r',257),('s',268),('t',268),('u',268),('v',268),('w',268),('x',268),('y',268),('z',268)]))" lx__270_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__270_0 = read "(False,[(35,\"tag\",[2,3],Nothing,Nothing)],-1,(('A','z'),[('A',270),('B',270),('C',270),('D',270),('E',270),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',270),('Q',270),('R',270),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',270),('c',270),('d',270),('e',270),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',270),('q',270),('r',270),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))" lx__271_0 :: (Bool, [(Int,String,[Int],Maybe((Char,Char),[(Char,Bool)]),Maybe Int)], Int, ((Char,Char),[(Char,Int)])) lx__271_0 = read "(False,[(35,\"tag\",[2,3],Nothing,Nothing)],-1,(('A','z'),[('A',270),('B',270),('C',270),('D',270),('E',270),('F',270),('G',270),('H',270),('I',270),('J',270),('K',270),('L',270),('M',270),('N',270),('O',270),('P',270),('Q',270),('R',262),('S',270),('T',270),('U',270),('V',270),('W',270),('X',270),('Y',270),('Z',270),('a',270),('b',270),('c',270),('d',270),('e',270),('f',270),('g',270),('h',270),('i',270),('j',270),('k',270),('l',270),('m',270),('n',270),('o',270),('p',270),('q',270),('r',262),('s',270),('t',270),('u',270),('v',270),('w',270),('x',270),('y',270),('z',270)]))"